Skip to content

Commit 761bb17

Browse files
author
Srinidh Jilla
committed
Implement COBOL line filtering and add tests for EJECT/SKIP handling
Signed-off-by: Srinidh Jilla <[email protected]>
1 parent 16ebdec commit 761bb17

File tree

8 files changed

+261
-0
lines changed

8 files changed

+261
-0
lines changed

src/main/cobol/TEST-FILTER.CBL

Lines changed: 43 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,43 @@
1+
IDENTIFICATION DIVISION.
2+
PROGRAM-ID. TEST-FILTER.
3+
4+
ENVIRONMENT DIVISION.
5+
6+
DATA DIVISION.
7+
WORKING-STORAGE SECTION.
8+
01 WS-TEST-VAR PIC X(10) VALUE SPACES. ABCD12
9+
01 WS-COUNTER PIC 9(3) VALUE 0.
10+
01 WS-RESULT PIC 9(3) VALUE 0.
11+
12+
PROCEDURE DIVISION.
13+
14+
MAIN-PROCESS.
15+
EJECT
16+
17+
MOVE "HELLO" TO WS-TEST-VAR
18+
MOVE 10 TO WS-COUNTER TEST1234
19+
20+
SKIP1
21+
22+
PERFORM CALCULATE-RESULT
23+
24+
EJECT
25+
26+
DISPLAY "Program completed successfully"
27+
.
28+
29+
PROGRAM-END.
30+
STOP RUN.
31+
32+
CALCULATE-RESULT.
33+
SKIP2
34+
COMPUTE WS-RESULT = WS-COUNTER * 2
35+
36+
EJECT
37+
38+
IF WS-RESULT > 15
39+
DISPLAY "Result is greater than 15: " WS-RESULT
40+
ELSE
41+
DISPLAY "Result is 15 or less: " WS-RESULT
42+
END-IF
43+
.

src/main/java/org/openmainframeproject/cobolcheck/features/interpreter/CobolReader.java

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
package org.openmainframeproject.cobolcheck.features.interpreter;
22

33
import org.openmainframeproject.cobolcheck.exceptions.PossibleInternalLogicErrorException;
4+
import org.openmainframeproject.cobolcheck.services.StringHelper;
45
import org.openmainframeproject.cobolcheck.services.cobolLogic.CobolLine;
56
import org.openmainframeproject.cobolcheck.services.cobolLogic.Interpreter;
67
import org.openmainframeproject.cobolcheck.services.cobolLogic.TokenExtractor;
@@ -64,6 +65,15 @@ CobolLine readLine() throws IOException {
6465
if (line == null){
6566
return null;
6667
}
68+
69+
// Comment out SKIP and EJECT pagination directives that are incompatible with GnuCOBOL
70+
if (StringHelper.shouldFilterLine(line)) {
71+
line = StringHelper.commentOutLine(StringHelper.removeRightSideSequenceNumbers(line));
72+
} else {
73+
// Always remove right-side sequence numbers from all lines to avoid processing issues
74+
line = StringHelper.removeRightSideSequenceNumbers(line);
75+
}
76+
6777
previousLine = currentLine;
6878
setPreviousMeaningfulLine();
6979
currentLine = new CobolLine(line, tokenExtractor);
@@ -214,6 +224,15 @@ CobolLine peekNextMeaningfulLine() throws IOException {
214224
if (line == null){
215225
return null;
216226
}
227+
228+
// Comment out SKIP and EJECT pagination directives that are incompatible with GnuCOBOL
229+
if (StringHelper.shouldFilterLine(line)) {
230+
line = StringHelper.commentOutLine(StringHelper.removeRightSideSequenceNumbers(line));
231+
} else {
232+
// Always remove right-side sequence numbers from all lines to avoid processing issues
233+
line = StringHelper.removeRightSideSequenceNumbers(line);
234+
}
235+
217236
CobolLine cobolLine = new CobolLine(line, tokenExtractor);
218237
nextLines.add(cobolLine);
219238
if (Interpreter.isMeaningful(cobolLine)){

src/main/java/org/openmainframeproject/cobolcheck/services/Constants.java

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -158,6 +158,9 @@ private Constants() {
158158
public static final String PICTURE_VALUE = "PICTURE";
159159
public static final String NUMERIC_PICTURE_CLAUSE_PATTERN = "^[\\d\\(\\)SsVv]+$";
160160

161+
// COBOL line column definitions
162+
public static final int COBOL_LINE_NUMBER_COLUMN_END = 6;
163+
public static final int COBOL_CODE_AREA_END = 72;
161164

162165
//Keywords not in COBOL-Code
163166
public static final String PARAGRAPH_TOKEN = "PARAGRAPH";

src/main/java/org/openmainframeproject/cobolcheck/services/StringHelper.java

Lines changed: 53 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -283,4 +283,57 @@ public static boolean startsWithAny(String value, Collection<String> collection)
283283
}
284284
return false;
285285
}
286+
287+
/**
288+
* Check if a line contains SKIP or EJECT pagination directives that should be filtered out
289+
* for GnuCOBOL compatibility
290+
*
291+
* @param sourceLine the COBOL source line to check
292+
* @return true if the line should be filtered (commented out)
293+
*/
294+
public static boolean shouldFilterLine(String sourceLine) {
295+
if (sourceLine == null || sourceLine.trim().isEmpty()) {
296+
return false;
297+
}
298+
299+
String lineContent = sourceLine.trim().toUpperCase();
300+
301+
// If line has line numbers, extract the content part
302+
if (sourceLine.length() > Constants.COBOL_LINE_NUMBER_COLUMN_END && Character.isDigit(sourceLine.charAt(0))) {
303+
lineContent = sourceLine.substring(Constants.COBOL_LINE_NUMBER_COLUMN_END).trim().toUpperCase();
304+
}
305+
306+
// Check if this line is EJECT or SKIP variant
307+
return lineContent.equals("EJECT") || lineContent.startsWith("SKIP");
308+
}
309+
310+
/**
311+
* Remove right-side sequence numbers (columns 73-80) from COBOL source lines
312+
* COBOL standard: columns 73-80 are identification area (right-side sequence numbers)
313+
* Only removes content if there are actual sequence numbers beyond column 72
314+
*
315+
* @param line the original COBOL line
316+
* @return the line with right-side sequence numbers removed if they exist
317+
*/
318+
public static String removeRightSideSequenceNumbers(String line) {
319+
if (line == null || line.length() <= Constants.COBOL_CODE_AREA_END) {
320+
return line;
321+
}
322+
323+
// Extract the potential sequence number area (columns 73-80)
324+
String sequenceArea = line.substring(Constants.COBOL_CODE_AREA_END);
325+
326+
// Only remove if the sequence area contains actual sequence numbers (not just spaces)
327+
// Sequence numbers are typically digits, or alphanumeric identifiers
328+
String trimmedSequenceArea = sequenceArea.trim();
329+
if (!trimmedSequenceArea.isEmpty()) {
330+
// Check if it looks like sequence numbers (digits, or mixed alphanumeric like "000010" or "A123")
331+
if (trimmedSequenceArea.matches("^[A-Z0-9]+$") && trimmedSequenceArea.length() <= 8) {
332+
return line.substring(0, Constants.COBOL_CODE_AREA_END);
333+
}
334+
}
335+
336+
// If it's just spaces or doesn't look like sequence numbers, keep the line as-is
337+
return line;
338+
}
286339
}
Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
TestSuite "Test EJECT and SKIP handling"
2+
3+
TestCase "Test basic functionality with EJECT/SKIP"
4+
Perform MAIN-PROCESS
5+
Expect WS-TEST-VAR = "HELLO "
6+
Expect WS-COUNTER = 10
7+
Expect WS-RESULT = 20
8+
9+
TestCase "Test calculation result"
10+
Move 5 to WS-COUNTER
11+
Perform CALCULATE-RESULT
12+
Expect WS-RESULT = 10
13+
14+
TestCase "Test calculation with larger number"
15+
Move 15 to WS-COUNTER
16+
Perform CALCULATE-RESULT
17+
Expect WS-RESULT = 30

src/test/java/org/openmainframeproject/cobolcheck/StringHelperTest.java

Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -153,4 +153,32 @@ public void it_stubs_a_line_that_starts_without_spaces_long_stub_tag() {
153153
String original = "CALL 'PROG1'.";
154154
assertEquals(expected, StringHelper.stubLine(original, "STUBBEDVALUE"));
155155
}
156+
157+
// Tests for COBOL line filtering functionality
158+
@Test
159+
public void shouldFilterLine_identifies_EJECT_statements() {
160+
assertTrue(StringHelper.shouldFilterLine(" EJECT"));
161+
assertTrue(StringHelper.shouldFilterLine("000010 EJECT"));
162+
assertFalse(StringHelper.shouldFilterLine(" CALL 'EJECT-PROG'"));
163+
}
164+
165+
@Test
166+
public void shouldFilterLine_identifies_SKIP_statements() {
167+
assertTrue(StringHelper.shouldFilterLine(" SKIP1"));
168+
assertTrue(StringHelper.shouldFilterLine(" SKIP"));
169+
assertFalse(StringHelper.shouldFilterLine(" DISPLAY 'SKIP THIS'"));
170+
}
171+
172+
@Test
173+
public void removeRightSideSequenceNumbers_removes_sequence_numbers() {
174+
String withSeqNum = " MOVE 1 TO A. 000010";
175+
String expected = " MOVE 1 TO A. ";
176+
assertEquals(expected, StringHelper.removeRightSideSequenceNumbers(withSeqNum));
177+
}
178+
179+
@Test
180+
public void removeRightSideSequenceNumbers_preserves_normal_lines() {
181+
String normal = " MOVE 1 TO A. ";
182+
assertEquals(normal, StringHelper.removeRightSideSequenceNumbers(normal));
183+
}
156184
}
Lines changed: 81 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,81 @@
1+
package org.openmainframeproject.cobolcheck.features.interpreter;
2+
3+
import org.junit.jupiter.api.Test;
4+
import org.openmainframeproject.cobolcheck.services.cobolLogic.CobolLine;
5+
6+
import java.io.BufferedReader;
7+
import java.io.IOException;
8+
import java.io.StringReader;
9+
10+
import static org.junit.jupiter.api.Assertions.*;
11+
12+
/**
13+
* Simple integration tests for COBOL line filtering in CobolReader
14+
*/
15+
public class CobolReaderLineFilteringTest {
16+
17+
@Test
18+
public void testEjectStatementIsCommentedOut() throws IOException {
19+
String cobolSource = String.join(System.lineSeparator(),
20+
" IDENTIFICATION DIVISION.",
21+
" EJECT",
22+
" DATA DIVISION."
23+
);
24+
25+
BufferedReader bufferedReader = new BufferedReader(new StringReader(cobolSource));
26+
CobolReader cobolReader = new CobolReader(bufferedReader);
27+
28+
CobolLine line1 = cobolReader.readLine();
29+
assertEquals(" IDENTIFICATION DIVISION.", line1.getOriginalString());
30+
31+
CobolLine line2 = cobolReader.readLine();
32+
assertEquals(" *EJECT", line2.getOriginalString()); // Should be commented out
33+
34+
CobolLine line3 = cobolReader.readLine();
35+
assertEquals(" DATA DIVISION.", line3.getOriginalString());
36+
37+
cobolReader.close();
38+
}
39+
40+
@Test
41+
public void testSkipStatementIsCommentedOut() throws IOException {
42+
String cobolSource = String.join(System.lineSeparator(),
43+
" PROCEDURE DIVISION.",
44+
" SKIP1",
45+
" DISPLAY 'HELLO'."
46+
);
47+
48+
BufferedReader bufferedReader = new BufferedReader(new StringReader(cobolSource));
49+
CobolReader cobolReader = new CobolReader(bufferedReader);
50+
51+
CobolLine line1 = cobolReader.readLine();
52+
assertEquals(" PROCEDURE DIVISION.", line1.getOriginalString());
53+
54+
CobolLine line2 = cobolReader.readLine();
55+
assertEquals(" *SKIP1", line2.getOriginalString()); // Should be commented out
56+
57+
CobolLine line3 = cobolReader.readLine();
58+
assertEquals(" DISPLAY 'HELLO'.", line3.getOriginalString());
59+
60+
cobolReader.close();
61+
}
62+
63+
@Test
64+
public void testSequenceNumbersAreRemoved() throws IOException {
65+
String cobolSource = String.join(System.lineSeparator(),
66+
" MOVE 1 TO A. 000010",
67+
" DISPLAY 'TEST'. ABC123"
68+
);
69+
70+
BufferedReader bufferedReader = new BufferedReader(new StringReader(cobolSource));
71+
CobolReader cobolReader = new CobolReader(bufferedReader);
72+
73+
CobolLine line1 = cobolReader.readLine();
74+
assertEquals(" MOVE 1 TO A. ", line1.getOriginalString());
75+
76+
CobolLine line2 = cobolReader.readLine();
77+
assertEquals(" DISPLAY 'TEST'. ", line2.getOriginalString());
78+
79+
cobolReader.close();
80+
}
81+
}

testruns/testResults.txt

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
TESTSUITE:
2+
Test EJECT and SKIP handling
3+
Result is greater than 15: 020
4+
Program completed successfully
5+
PASS: 1. Test basic functionality with EJECT/SKIP
6+
PASS: 2. Test basic functionality with EJECT/SKIP
7+
PASS: 3. Test basic functionality with EJECT/SKIP
8+
Result is 15 or less: 010
9+
PASS: 4. Test calculation result
10+
Result is greater than 15: 030
11+
PASS: 5. Test calculation with larger number
12+
13+
5 TEST CASES WERE EXECUTED
14+
5 PASSED
15+
0 FAILED
16+
0 CALLS NOT MOCKED
17+
=================================================

0 commit comments

Comments
 (0)