Skip to content

Commit 697cde4

Browse files
authored
Error handling after increasing the array index
After increasing the array index, an error handling must be included, because if the input is extended later again, we can look for the error again. A handled error is easier to find and fix than a buffer overwrite error. Table index should start from 0, because it indicates better that the table is empty. Signed-off-by: Janos Varga <113785741+vargajb@users.noreply.github.com>
1 parent c924f44 commit 697cde4

File tree

1 file changed

+13
-4
lines changed
  • COBOL Programming Course #3 - Advanced Topics/Challenges/Debugging/cbl

1 file changed

+13
-4
lines changed

COBOL Programming Course #3 - Advanced Topics/Challenges/Debugging/cbl/CBL0106C.cbl

Lines changed: 13 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -44,9 +44,10 @@
4444
*
4545
WORKING-STORAGE SECTION.
4646
01 Filler.
47-
05 LASTREC PIC X VALUE SPACE.
47+
05 LASTREC PIC X VALUE SPACE.
4848
05 DISP-SUB1 PIC 9999.
4949
05 SUB1 PIC 99.
50+
05 OVERLIMIT-MAX PIC S9(4) COMP VALUE 20.
5051

5152
01 OVERLIMIT.
5253
03 FILLER OCCURS 20 TIMES.
@@ -136,7 +137,7 @@
136137
WRITE PRINT-REC FROM HEADER-3.
137138
WRITE PRINT-REC FROM HEADER-4.
138139
MOVE SPACES TO PRINT-REC.
139-
MOVE 1 TO SUB1.
140+
MOVE 0 TO SUB1.
140141
*
141142
READ-NEXT-RECORD.
142143
PERFORM READ-RECORD
@@ -162,11 +163,19 @@
162163
*
163164
IS-OVERLIMIT.
164165
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 'OVERFOLW TABLE OVERLIMIT'
172+
MOVE 1000 TO RETURN-CODE
173+
STOP RUN
174+
END-IF
165175
MOVE ACCT-LIMIT TO OL-ACCT-LIMIT(SUB1)
166176
MOVE ACCT-BALANCE TO OL-ACCT-BALANCE(SUB1)
167177
MOVE LAST-NAME TO OL-LASTNAME(SUB1)
168178
MOVE FIRST-NAME TO OL-FIRSTNAME(SUB1)
169-
ADD 1 TO SUB1
170179
END-IF.
171180
*
172181
IS-STATE-VIRGINIA.
@@ -175,7 +184,7 @@
175184
END-IF.
176185
*
177186
WRITE-OVERLIMIT.
178-
IF SUB1 = 1 THEN
187+
IF SUB1 = 0 THEN
179188
MOVE OVERLIMIT-STATUS TO PRINT-REC
180189
WRITE PRINT-REC
181190
ELSE

0 commit comments

Comments
 (0)