Skip to content

Commit 74b6f2c

Browse files
authored
Merge pull request #396 from openmainframeproject/remote-extra-line-numbers
Remote extra line numbers
2 parents bc56851 + 4cec4b9 commit 74b6f2c

File tree

19 files changed

+223
-90
lines changed

19 files changed

+223
-90
lines changed

CHANGELOG.md

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,9 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0
2020
- Mock SQL tables
2121
- Mock batch file I/O
2222

23+
## \[0.2.18\] 2025-06-02
24+
- Sequence numbers are handled correct in long lines
25+
2326
## \[0.2.17\] 2025-04-02
2427
- Made sure we are using the correct encoding
2528

approvaltestWin.cmd

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1 +1 @@
1-
./cobolcheck -p ALPHA DB2PROG DPICNUMBERS FILECOPY GREETING MOCK MOCKPARA MOCKTEST NUMBERS RETURNCODE TESTNESTED > approval-test-actual.txt
1+
./cobolcheck -p ALPHA DB2PROG DPICNUMBERS FILECOPY GREETING MOCK MOCKPARA MOCKTEST NUMBERS RETURNCODE TESTNESTED LONGLINESANDNUMBERS > approval-test-actual.txt

build.gradle

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ plugins {
66
id 'jacoco'
77
}
88

9-
def productVersion = '0.2.17'
9+
def productVersion = '0.2.18'
1010
def productName = 'cobol-check'
1111
group = 'org.openmainframeproject'
1212
description = 'Unit testing framework for Cobol'
238 KB
Binary file not shown.
Lines changed: 65 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,65 @@
1+
000100 IDENTIFICATION DIVISION.
2+
000200 PROGRAM-ID. GREETING.
3+
000300*****************************************************************
4+
000400* Trivial program to exercise CobolCheck.
5+
000500*****************************************************************
6+
000600 ENVIRONMENT DIVISION.
7+
000700 INPUT-OUTPUT SECTION.
8+
000800 FILE-CONTROL.
9+
000900 DATA DIVISION.
10+
001000 WORKING-STORAGE SECTION.
11+
001100 01 FILLER.
12+
001200 05 WS-COUNT PIC S9(5) COMP-3.
13+
001300 05 FILLER PIC X VALUE 'G'.
14+
001400 88 MESSAGE-IS-GREETING VALUE 'G'.
15+
001500 88 MESSAGE-IS-FAREWELL VALUE 'F'.
16+
001600 88 MESSAGE-IS-FAREWELL-LONG VALUE 'L'.
17+
001700 01 WS-FRIEND PIC X(10) VALUE SPACES.
18+
001800 01 WS-GREETING.
19+
001900 10 FILLER PIC X(07) VALUE 'Hello, '.
20+
002000 10 WS-USER-NAME PIC X(05) VALUE SPACES.
21+
002100 10 FILLER PIC X VALUE '!'.
22+
002200 01 WS-FAREWELL.
23+
002300 10 FILLER PIC X(15) VALUE 'See you later, '.
24+
002400 10 WS-USER-NAME PIC X(09) VALUE SPACES.
25+
002500 10 FILLER PIC X VALUE '!'.
26+
002600 01 WS-FAREWELL-LONG.
27+
002700 10 FILLER PIC X(15) VALUE 'See you later, '.
28+
002800 10 WS-USER-NAME-LONG PIC X(19) VALUE SPACES.
29+
002900 10 FILLER PIC X VALUE '!'.
30+
003000 REPLACE
31+
003100 ==:TEXT:== BY =="ReallylongAlligator"==.
32+
003200
33+
003300 PROCEDURE DIVISION.
34+
003400
35+
003500 ACCEPT WS-FRIEND.
36+
003600
37+
003700 2000-SPEAK.
38+
003800 IF MESSAGE-IS-GREETING
39+
003900 IF WS-FRIEND EQUAL SPACES
40+
004000 MOVE 'World' TO WS-USER-NAME OF WS-GREETING
41+
004100 ELSE
42+
004200 MOVE WS-FRIEND TO WS-USER-NAME OF WS-GREETING
43+
004300 END-IF
44+
004400 END-IF
45+
004500 IF MESSAGE-IS-FAREWELL
46+
004600 IF WS-FRIEND EQUAL SPACES
47+
004700 MOVE 'alligator!' TO WS-USER-NAME OF WS-FAREWELL
48+
004800 ELSE
49+
004900 MOVE WS-FRIEND TO WS-USER-NAME OF WS-FAREWELL
50+
005000 END-IF
51+
005100 END-IF
52+
005200 IF MESSAGE-IS-FAREWELL-LONG
53+
005300 IF WS-FRIEND EQUAL SPACES
54+
005400 MOVE :TEXT: TO WS-USER-NAME-LONG OF WS-FAREWELL-LONG
55+
005500 ELSE
56+
005600 MOVE WS-FRIEND TO WS-USER-NAME-LONG
57+
005700 OF WS-FAREWELL-LONG
58+
005800 END-IF
59+
005900 END-IF
60+
006000 .
61+
006100
62+
006200 9999-END.
63+
006300 CONTINUE
64+
006400 .
65+
006500

src/main/java/org/openmainframeproject/cobolcheck/features/writer/CobolWriter.java

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -160,6 +160,11 @@ void close() throws IOException {
160160
* @throws IOException - pass any IOExceptions to the caller.
161161
*/
162162
private void writeMultiLine(String line, boolean isComment, boolean isRecursiveCall) throws IOException {
163+
String saveNumbers = "";
164+
if (line.matches("^\\d{6}.*")) {
165+
saveNumbers = line.substring(0,6);
166+
line = line.replaceFirst("^\\d{6}", " ");
167+
}
163168
String line1 = line.substring(0,maxLineLength);
164169
String line2 = line.substring(maxLineLength);
165170
if (line2.length() > 0 && !isComment) {
@@ -197,6 +202,9 @@ else if (isRecursiveCall)
197202
}
198203
}
199204
}
205+
if (!saveNumbers.isEmpty()) {
206+
line1 = line1.replaceFirst(" ", saveNumbers);
207+
}
200208
writeLine(line1);
201209
}
202210
else if (line2.length() > 0 && isComment){

src/main/java/org/openmainframeproject/cobolcheck/workers/Initializer.java

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ public class Initializer {
2121
private StatusController statusController;
2222

2323
public Initializer(String[] args) {
24-
Log.info(Messages.get("INF000", "0.2.17"));
24+
Log.info(Messages.get("INF000", "0.2.18"));
2525
argumentController = new ArgumentHandlerController(args);
2626
environmentController = new EnvironmentSetupController();
2727
statusController = new StatusController();
Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
TESTSUITE
2+
"Greeting includes the user name when it is provided"
3+
4+
TESTCASE "When message type is greeting it returns Hello, James!"
5+
SET MESSAGE-IS-GREETING TO TRUE
6+
MOVE "James" TO WS-FRIEND
7+
PERFORM 2000-SPEAK
8+
EXPECT WS-GREETING TO BE "Hello, James!"
9+
10+
TESTCASE "When message type is farewell it returns Goodbye, James !"
11+
SET MESSAGE-IS-FAREWELL TO TRUE
12+
MOVE "James" TO WS-FRIEND
13+
PERFORM 2000-SPEAK
14+
EXPECT WS-FAREWELL TO BE "See you later, James !"
15+
16+
TESTCASE "User name for greeting and farewell are consistent"
17+
SET MESSAGE-IS-GREETING TO TRUE
18+
Move "Henry" TO WS-FRIEND
19+
PERFORM 2000-SPEAK
20+
EXPECT WS-USER-NAME OF WS-GREETING TO BE "Henry"
Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
TESTSUITE
2+
"Greeting returns the appropriate message based on message type"
3+
4+
TestCase "When message type is greeting it returns 'Hello, World!'"
5+
move space to WS-FRIEND
6+
SET MESSAGE-IS-GREETING TO TRUE
7+
PERFORM 2000-SPEAK
8+
EXPECT WS-GREETING TO BE "Hello, World!"
9+
10+
TESTCASE "try numerical compare"
11+
ADD 1 TO WS-COUNT
12+
EXPECT WS-COUNT TO BE 1
13+
14+
TESTCASE "try 88 level compare"
15+
set message-is-farewell to true
16+
EXPECT MESSAGE-IS-GREETING TO BE FALSE
17+
18+
TESTCASE "When message type is farewell it returns See you later, alligator!"
19+
SET MESSAGE-IS-FAREWELL-LONG TO TRUE
20+
PERFORM 2000-SPEAK
21+
Expect WS-FAREWELL-LONG To Be "See you later, ReallylongAlligator!"
22+
23+
TESTCASE "Message type greeting is not true"
24+
SET MESSAGE-IS-FAREWELL TO TRUE
25+
Expect MESSAGE-IS-GREETING NOT TO BE TRUE
26+

vs-code-extension/CHANGELOG.md

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,9 @@
22

33
All notable changes to the "cobol-unit-test" extension will be documented in this file. Versioning according to SemVer: https://semver.org/
44

5+
## [0.4.12] 02.06.2025
6+
- Now using COBOL Check version 0.2.18
7+
58
## [0.4.11] 02.04.2025
69
- Now using COBOL Check version 0.2.17
710

0 commit comments

Comments
 (0)