Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
3 changes: 3 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,9 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0
- Mock SQL tables
- Mock batch file I/O

## \[0.2.18\] 2025-06-02
- Sequence numbers are handled correct in long lines

## \[0.2.17\] 2025-04-02
- Made sure we are using the correct encoding

Expand Down
2 changes: 1 addition & 1 deletion approvaltestWin.cmd
Original file line number Diff line number Diff line change
@@ -1 +1 @@
./cobolcheck -p ALPHA DB2PROG DPICNUMBERS FILECOPY GREETING MOCK MOCKPARA MOCKTEST NUMBERS RETURNCODE TESTNESTED > approval-test-actual.txt
./cobolcheck -p ALPHA DB2PROG DPICNUMBERS FILECOPY GREETING MOCK MOCKPARA MOCKTEST NUMBERS RETURNCODE TESTNESTED LONGLINESANDNUMBERS > approval-test-actual.txt
2 changes: 1 addition & 1 deletion build.gradle
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ plugins {
id 'jacoco'
}

def productVersion = '0.2.17'
def productVersion = '0.2.18'
def productName = 'cobol-check'
group = 'org.openmainframeproject'
description = 'Unit testing framework for Cobol'
Expand Down
Binary file added build/distributions/cobol-check-0.2.18.zip
Binary file not shown.
65 changes: 65 additions & 0 deletions src/main/cobol/LONGLINESANDNUMBERS.CBL
Original file line number Diff line number Diff line change
@@ -0,0 +1,65 @@
000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. GREETING.
000300*****************************************************************
000400* Trivial program to exercise CobolCheck.
000500*****************************************************************
000600 ENVIRONMENT DIVISION.
000700 INPUT-OUTPUT SECTION.
000800 FILE-CONTROL.
000900 DATA DIVISION.
001000 WORKING-STORAGE SECTION.
001100 01 FILLER.
001200 05 WS-COUNT PIC S9(5) COMP-3.
001300 05 FILLER PIC X VALUE 'G'.
001400 88 MESSAGE-IS-GREETING VALUE 'G'.
001500 88 MESSAGE-IS-FAREWELL VALUE 'F'.
001600 88 MESSAGE-IS-FAREWELL-LONG VALUE 'L'.
001700 01 WS-FRIEND PIC X(10) VALUE SPACES.
001800 01 WS-GREETING.
001900 10 FILLER PIC X(07) VALUE 'Hello, '.
002000 10 WS-USER-NAME PIC X(05) VALUE SPACES.
002100 10 FILLER PIC X VALUE '!'.
002200 01 WS-FAREWELL.
002300 10 FILLER PIC X(15) VALUE 'See you later, '.
002400 10 WS-USER-NAME PIC X(09) VALUE SPACES.
002500 10 FILLER PIC X VALUE '!'.
002600 01 WS-FAREWELL-LONG.
002700 10 FILLER PIC X(15) VALUE 'See you later, '.
002800 10 WS-USER-NAME-LONG PIC X(19) VALUE SPACES.
002900 10 FILLER PIC X VALUE '!'.
003000 REPLACE
003100 ==:TEXT:== BY =="ReallylongAlligator"==.
003200
003300 PROCEDURE DIVISION.
003400
003500 ACCEPT WS-FRIEND.
003600
003700 2000-SPEAK.
003800 IF MESSAGE-IS-GREETING
003900 IF WS-FRIEND EQUAL SPACES
004000 MOVE 'World' TO WS-USER-NAME OF WS-GREETING
004100 ELSE
004200 MOVE WS-FRIEND TO WS-USER-NAME OF WS-GREETING
004300 END-IF
004400 END-IF
004500 IF MESSAGE-IS-FAREWELL
004600 IF WS-FRIEND EQUAL SPACES
004700 MOVE 'alligator!' TO WS-USER-NAME OF WS-FAREWELL
004800 ELSE
004900 MOVE WS-FRIEND TO WS-USER-NAME OF WS-FAREWELL
005000 END-IF
005100 END-IF
005200 IF MESSAGE-IS-FAREWELL-LONG
005300 IF WS-FRIEND EQUAL SPACES
005400 MOVE :TEXT: TO WS-USER-NAME-LONG OF WS-FAREWELL-LONG
005500 ELSE
005600 MOVE WS-FRIEND TO WS-USER-NAME-LONG
005700 OF WS-FAREWELL-LONG
005800 END-IF
005900 END-IF
006000 .
006100
006200 9999-END.
006300 CONTINUE
006400 .
006500
Original file line number Diff line number Diff line change
Expand Up @@ -160,6 +160,11 @@ void close() throws IOException {
* @throws IOException - pass any IOExceptions to the caller.
*/
private void writeMultiLine(String line, boolean isComment, boolean isRecursiveCall) throws IOException {
String saveNumbers = "";
if (line.matches("^\\d{6}.*")) {
saveNumbers = line.substring(0,6);
line = line.replaceFirst("^\\d{6}", " ");
}
String line1 = line.substring(0,maxLineLength);
String line2 = line.substring(maxLineLength);
if (line2.length() > 0 && !isComment) {
Expand Down Expand Up @@ -197,6 +202,9 @@ else if (isRecursiveCall)
}
}
}
if (!saveNumbers.isEmpty()) {
line1 = line1.replaceFirst(" ", saveNumbers);
}
writeLine(line1);
}
else if (line2.length() > 0 && isComment){
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ public class Initializer {
private StatusController statusController;

public Initializer(String[] args) {
Log.info(Messages.get("INF000", "0.2.17"));
Log.info(Messages.get("INF000", "0.2.18"));
argumentController = new ArgumentHandlerController(args);
environmentController = new EnvironmentSetupController();
statusController = new StatusController();
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
TESTSUITE
"Greeting includes the user name when it is provided"

TESTCASE "When message type is greeting it returns Hello, James!"
SET MESSAGE-IS-GREETING TO TRUE
MOVE "James" TO WS-FRIEND
PERFORM 2000-SPEAK
EXPECT WS-GREETING TO BE "Hello, James!"

TESTCASE "When message type is farewell it returns Goodbye, James !"
SET MESSAGE-IS-FAREWELL TO TRUE
MOVE "James" TO WS-FRIEND
PERFORM 2000-SPEAK
EXPECT WS-FAREWELL TO BE "See you later, James !"

TESTCASE "User name for greeting and farewell are consistent"
SET MESSAGE-IS-GREETING TO TRUE
Move "Henry" TO WS-FRIEND
PERFORM 2000-SPEAK
EXPECT WS-USER-NAME OF WS-GREETING TO BE "Henry"
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
TESTSUITE
"Greeting returns the appropriate message based on message type"

TestCase "When message type is greeting it returns 'Hello, World!'"
move space to WS-FRIEND
SET MESSAGE-IS-GREETING TO TRUE
PERFORM 2000-SPEAK
EXPECT WS-GREETING TO BE "Hello, World!"

TESTCASE "try numerical compare"
ADD 1 TO WS-COUNT
EXPECT WS-COUNT TO BE 1

TESTCASE "try 88 level compare"
set message-is-farewell to true
EXPECT MESSAGE-IS-GREETING TO BE FALSE

TESTCASE "When message type is farewell it returns See you later, alligator!"
SET MESSAGE-IS-FAREWELL-LONG TO TRUE
PERFORM 2000-SPEAK
Expect WS-FAREWELL-LONG To Be "See you later, ReallylongAlligator!"

TESTCASE "Message type greeting is not true"
SET MESSAGE-IS-FAREWELL TO TRUE
Expect MESSAGE-IS-GREETING NOT TO BE TRUE

3 changes: 3 additions & 0 deletions vs-code-extension/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,9 @@

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

## [0.4.12] 02.06.2025
- Now using COBOL Check version 0.2.18

## [0.4.11] 02.04.2025
- Now using COBOL Check version 0.2.17

Expand Down
Binary file not shown.
Binary file not shown.
1 change: 1 addition & 0 deletions vs-code-extension/Cobol-check/src/main/cobol/ALPHA.CBL
Original file line number Diff line number Diff line change
Expand Up @@ -24,3 +24,4 @@
05 ws-display-numeric pic 999.
PROCEDURE DIVISION.
GOBACK.

3 changes: 3 additions & 0 deletions vs-code-extension/Cobol-check/src/main/cobol/NUMBERS.CBL
Original file line number Diff line number Diff line change
Expand Up @@ -14,5 +14,8 @@
05 ws-field-3 pic s9(16) comp.
05 ws-field-4 pic s9(16) comp-4.
05 ws-display-field pic s9(5)v99.
05 ws-num-occ pic 9(04) occurs 10.
77 CHAR-CT PIC S9(3) COMP.
PROCEDURE DIVISION.
GOBACK.

Original file line number Diff line number Diff line change
@@ -1,61 +1,66 @@
TestSuite "Tests of alphanumeric expectations"

TestCase "Equality with an alphanumeric literal using TO BE"
move "value1" to ws-field-1
Expect ws-field-1 to be "value1"

TestCase "Equality with an alphanumeric literal using TO EQUAL"
move "value2" to ws-field-1
Expect ws-field-1 to equal "value2"

TestCase "Equality with an alphanumeric literal using '='"
move "value3" to ws-field-1
Expect ws-field-1 = "value3"

TestCase "Equality with an alphanumeric literal and reference modification"
move "Hello, World!" to ws-field-2
Expect ws-field-2(8:5) to be "World"

TestCase "Non-equality with an alphanumeric literal using TO BE"
move "value4" to ws-field-1
Expect ws-field-1 not to be "value1"

TestCase "Non-equality with an alphanumeric literal using TO EQUAL"
move "value5" to ws-field-1
Expect ws-field-1 not to equal "value1"

TestCase "Non-equality with an alphanumeric literal using '!='"
move "value6" to ws-field-1
Expect ws-field-1 != "value1"

TestCase "Non-equality with an alphanumeric literal and reference modification"
move "Hello, World!" to ws-field-2
Expect ws-field-2(8:6) not to be "World"

TestCase "Greater-than sign with an alphanumeric literal"
move "Beta" to ws-field-1
move "Alpha" to ws-field-2
Expect ws-field-1 > ws-field-2

Expect ws-field-1 > "Alpha"
TestCase "Less-than sign with an alphanumeric literal"
move "Beta" to ws-field-1
move "Alpha" to ws-field-2
Expect ws-field-2 < ws-field-1

Expect ws-field-2 < "Beta"
TestCase "Not greater-than sign with an alphanumeric literal"
move "Beta" to ws-field-1
move "Alpha" to ws-field-2
Expect ws-field-2 not > ws-field-1

Expect ws-field-2 not > "Beta"
TestCase "Not less-than sign with an alphanumeric literal"
move "Beta" to ws-field-1
move "Alpha" to ws-field-2
Expect ws-field-1 not < ws-field-2

Expect ws-field-1 not < "Alpha"
TestCase "Display numeric"
move 6 to ws-display-numeric
expect ws-display-numeric to be 6





TestCase "Variable must be SPACE"
move space to ws-field-1
expect ws-field-1 to be space

TestCase "Variable must be SPACES"
move spaces to ws-field-1
expect ws-field-1 to be spaces

Loading
Loading