File tree Expand file tree Collapse file tree 1 file changed +13
-4
lines changed
COBOL Programming Course #3 - Advanced Topics/Challenges/Debugging/cbl Expand file tree Collapse file tree 1 file changed +13
-4
lines changed Original file line number Diff line number Diff line change 44
44
*
45
45
WORKING-STORAGE SECTION .
46
46
01 Filler .
47
- 05 LASTREC PIC X VALUE SPACE .
47
+ 05 LASTREC PIC X VALUE SPACE .
48
48
05 DISP-SUB1 PIC 9999.
49
49
05 SUB1 PIC 99.
50
+ 05 OVERLIMIT-MAX PIC S9 (4 ) COMP VALUE 20 .
50
51
51
52
01 OVERLIMIT.
52
53
03 FILLER OCCURS 20 TIMES .
136
137
WRITE PRINT-REC FROM HEADER-3.
137
138
WRITE PRINT-REC FROM HEADER-4.
138
139
MOVE SPACES TO PRINT-REC.
139
- MOVE 1 TO SUB1.
140
+ MOVE 0 TO SUB1.
140
141
*
141
142
READ-NEXT-RECORD.
142
143
PERFORM READ-RECORD
162
163
*
163
164
IS-OVERLIMIT.
164
165
IF ACCT-LIMIT < ACCT-BALANCE THEN
166
+ ADD 1 TO SUB1
167
+ * Check if there is enough space in the array, in case the input
168
+ * file changes again. A handled error is easier to find and fix
169
+ * than a buffer overwrite error.
170
+ IF SUB1 > OVERLIMIT-MAX THEN
171
+ DISPLAY ' OVERFLOW TABLE OVERLIMIT'
172
+ MOVE 1000 TO RETURN-CODE
173
+ STOP RUN
174
+ END-IF
165
175
MOVE ACCT-LIMIT TO OL-ACCT-LIMIT(SUB1)
166
176
MOVE ACCT-BALANCE TO OL-ACCT-BALANCE(SUB1)
167
177
MOVE LAST-NAME TO OL-LASTNAME(SUB1)
168
178
MOVE FIRST-NAME TO OL-FIRSTNAME(SUB1)
169
- ADD 1 TO SUB1
170
179
END-IF .
171
180
*
172
181
IS-STATE-VIRGINIA.
175
184
END-IF .
176
185
*
177
186
WRITE-OVERLIMIT.
178
- IF SUB1 = 1 THEN
187
+ IF SUB1 = 0 THEN
179
188
MOVE OVERLIMIT-STATUS TO PRINT-REC
180
189
WRITE PRINT-REC
181
190
ELSE
You can’t perform that action at this time.
0 commit comments