Adding two integers giving unwanted result in cobol

北城以北 提交于 2021-02-19 07:40:28

问题


I'm reading a file into a table, note the first line is not part of the table.

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            

In the code, the table is represented as follows:

01     GRADES.
05         GRADE OCCURS 1 TO 100 TIMES DEPENDING ON RECORD-COUNT INDEXED BY J.
10            ASSIGNMENT-NAME   PIC X(20).
10            CATEGORY          PIC X(20).
10            POINTS-POSSIBLE   PIC 9(14).
10            POINTS-EARNED     PIC 9(14).

I have a few other accumulator variables designated for calculating sums/percentages later on.

01     RECORD-COUNT             PIC 9(8) VALUE 0.
01     TOTAL-EARNED-POINTS      PIC 9(14).
01     TOTAL-POSSIBLE-POINTS    PIC 9(14) VALUE 0.

My issue is, while I'm reading the records, line by line, I want to do the following:

ADD POINTS-EARNED(RECORD-COUNT) TO TOTAL-EARNED-POINTS

Where RECORD-COUNT is the current position in the iteration. I expect the value of TOTAL-EARNED-POINTS after the first iteration to simply be 5, right? However, when I DISPLAY the value of TOTAL-EARNED-POINTS, the console reads:

50000000000000

Is this 50 trillion? Or is it a funny looking representation of the number 5? How can I write this so that I can do proper mathematics with it to print a proper grade report?

EDIT: I know it's likely that there's better ways of writing this program but I've never used cobol before attempting to write this program, and I probably won't use it ever again, or at least for a very long time. This is for a class, so as long as I can print my output properly, I'm good. Full code, so far:

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 INDEXED BY I.
10            INPUT-ASSIGNMENT-NAME   PIC X(20).
10            INPUT-CATEGORY          PIC X(20).
10            INPUT-POINTS-POSSIBLE   PIC 9(14).
10            INPUT-POINTS-EARNED     PIC 9(14).

WORKING-STORAGE SECTION.
77     GRADES-FILE-EOF          PIC 9.
01     RECORD-COUNT             PIC 9(8) VALUE 0.
01     TOTAL-EARNED-POINTS      PIC 9(4) 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 INDEXED BY J.
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-GRADES TO GRADE(RECORD-COUNT)
                 SET TOTAL-EARNED-POINTS UP BY 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.

Edit 2: Upon implementing the given answer to convert the input from the file to a numeric form, the FIRST ROW of the table reads fine, but from then on it's all blank values. Here's the READ block's new code, I'm not sure if there's a more efficient way to read and convert specific fields in a group field but this is how I assumed it should be done.

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.

回答1:


is it a funny looking representation of the number 5?

No, it is an unchecked fatal exception: EC-DATA-INCOMPATIBLE.

The reason:
Your data definition and record-definition doesn't match:

10 POINTS-EARNED PIC 9(14).

would be

 "00000000000005"

not

 "5             "

which looks like the better definition for would be

10 SOME-POSSIBILY-NUMERIC-DATA PIC X(14).

If you use GnuCOBOL as the tags suggest, then add -debug to the compile command and you will see the fatal exception stopping the program (the COBOL standard defines that all exception checking is off by default, in my opinion: because of legacy and performance, but at least for developing and testing it is very reasonable to activate them [in most cases it is even more reasonable to let the program abend instead of doing wrong math when the test is over]).

As with any computer language you should be very sure to have valid data (never trust external data, no matter if it is part of a blockchain or a text file you read in).

How can I write this so that I can do proper mathematics with it to print a proper grade report?

If you want to go with "bad data is just ignored" (which may be appropriate here) just convert it:

MOVE FUNCTION NUMVAL (SOME-POSSIBILY-NUMERIC-DATA)
  TO POINTS-EARNED(RECORD-COUNT)

Otherwise do an explicit check (either of completely numeric [own check], or numeric with possible spaces to the left/right FUNCTION TEST-NUMVAL) and stop the program/skip the bad line with a DISPLAY ... UPON SYSERR or whatever is appropriate for you.



来源:https://stackoverflow.com/questions/63988919/adding-two-integers-giving-unwanted-result-in-cobol

标签
易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!