Skip to content

Commit

Permalink
Merge pull request #351 from openmainframeproject/DDH-13425-error-whe…
Browse files Browse the repository at this point in the history
…n-running-on-Linux-

Ddh 13425 error when running on linux
  • Loading branch information
oakmount1966 authored Sep 20, 2024
2 parents 652c061 + 54759cb commit 312dc67
Show file tree
Hide file tree
Showing 17 changed files with 39 additions and 31 deletions.
5 changes: 3 additions & 2 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -20,12 +20,13 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0
- Mock SQL tables
- Mock batch file I/O

## \[0.2.11\] 2024-05-13
- Fixing bug when cobolcheck.test.program.name was ending with white spaces.

## \[0.2.10\] 2024-05-13
### Not released
- Fixing bug in showing unit test result twice.

## \[0.2.9\] 2024-04-23
### Not released
- Better thread handling of the files processInput and processError


Expand Down
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.10'
def productVersion = '0.2.11'
def productName = 'cobol-check'
group = 'org.openmainframeproject'
description = 'Unit testing framework for Cobol'
Expand Down
Binary file added build/distributions/cobol-check-0.2.11.zip
Binary file not shown.
4 changes: 1 addition & 3 deletions scripts/linux_gnucobol_run_tests
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,4 @@
# GnuCOBOL 2.2 or later is installed and on the path. Its executable or alias or symlink is named "cobc".

cd "$(dirname $1)"
cobc -xj $@
name=$(echo "$1" | cut -f 1 -d '.')
"${name}"
cobc -xj $@
1 change: 1 addition & 0 deletions 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.
1 change: 1 addition & 0 deletions src/main/cobol/NUMBERS.CBL
Original file line number Diff line number Diff line change
Expand Up @@ -18,3 +18,4 @@
77 CHAR-CT PIC S9(3) COMP.
PROCEDURE DIVISION.
GOBACK.
7 changes: 5 additions & 2 deletions src/main/java/org/openmainframeproject/cobolcheck/Main.java
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,11 @@ public static void main(String[] args) throws InterruptedException {

generator.prepareAndRunMerge(programName, initializer.getTestFileNames());

if (initializer.launchTestProgram())
testRunner.run(programName, initializer.isLastSourceProgram(programName));
if (initializer.launchTestProgram()) {
int exitCode = testRunner.run(programName, initializer.isLastSourceProgram(programName));
if (exitCode >= 4)
initializer.setExitStatusHalt();
}
}

initializer.exitProgram();
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,5 @@ public void emitHelp()
public void exitProgram(){
Log.info(Messages.get("INF004") + ": " + status.exitStatus);
System.exit(status.exitStatus);

}
}
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ int launchProgram(ProcessLauncher launcher, String programPath) throws Interrupt
Process process = launcher.run(programPath);
int exitCode = 1;
exitCode = process.waitFor();
return exitCode;
return exitCode;
}

/**
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ public LauncherController(){
*
* @throws InterruptedException - pass any InterruptedException to the caller.
*/
public void runTestProgram(String programName, boolean isLastRun) throws InterruptedException {
public int runTestProgram(String programName, boolean isLastRun) throws InterruptedException {
// Compile and run the test program
ProcessLauncher pLauncher = launcher.getPlatformSpecificLauncher(PlatformLookup.get());
String processConfigKey = pLauncher.getProcessConfigKeyPrefix() + Constants.PROCESS_CONFIG_KEY;
Expand All @@ -44,5 +44,6 @@ public void runTestProgram(String programName, boolean isLastRun) throws Interru
Log.info(Messages.get("INF011", processName, processOutputWriter.getTestResultsFilePath()));
}
Log.info(Messages.get("INF009", processName, String.valueOf(exitCode)));
return exitCode;
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -211,7 +211,7 @@ public static String getTestResultFilePathString() {
static String generatedTestFileName = "";
public static String getGeneratedTestFileName() {
if (generatedTestFileName.isEmpty()){
generatedTestFileName = settings.getProperty(Constants.TEST_PROGRAM_NAME_CONFIG_KEY, Constants.CURRENT_DIRECTORY);
generatedTestFileName = settings.getProperty(Constants.TEST_PROGRAM_NAME_CONFIG_KEY, Constants.CURRENT_DIRECTORY).trim();
}
return generatedTestFileName;
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -14,9 +14,10 @@ public class CobolTestRunner {
*
* @throws InterruptedException - pass any InterruptedException up to the caller
*/
public void run(String programName, boolean isLastRun) throws InterruptedException {
public int run(String programName, boolean isLastRun) throws InterruptedException {
Path path = Paths.get(programName);
programName = path.getFileName().toString();
controller.runTestProgram(programName, isLastRun);
int exitCode = controller.runTestProgram(programName, isLastRun);
return exitCode;
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -72,4 +72,7 @@ public boolean launchTestProgram(){
return Config.getRunGeneratedTest();
}

public void setExitStatusHalt() {
statusController.setExitStatusHalt();
}
}
30 changes: 15 additions & 15 deletions src/test/cobol/ALPHA/AlphaExpectationsTest.cut
Original file line number Diff line number Diff line change
@@ -1,65 +1,65 @@
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 > "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 < "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 > "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 < "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
Expand Down
Binary file not shown.
2 changes: 1 addition & 1 deletion vs-code-extension/client/src/extension.ts
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ import { getContentFromFilesystem, MarkdownTestData, TestCase, testData, TestFil
let externalVsCodeInstallationDir = vscode.extensions.getExtension("openmainframeproject.cobol-check-extension").extensionPath;
let configPath = appendPath(externalVsCodeInstallationDir, 'Cobol-check/config.properties');
let defaultConfigPath = appendPath(externalVsCodeInstallationDir, 'Cobol-check/default.properties');
let cobolCheckJarPath = appendPath(externalVsCodeInstallationDir, 'Cobol-check/bin/cobol-check-0.2.10.jar');
let cobolCheckJarPath = appendPath(externalVsCodeInstallationDir, 'Cobol-check/bin/cobol-check-0.2.11.jar');
let currentPlatform = getOS();


Expand Down
2 changes: 1 addition & 1 deletion vs-code-extension/client/src/services/TestTree.ts
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ import { handleCobolCheckOut } from '../Helpers/ExtensionHelper';
const textDecoder = new TextDecoder('utf-8');
let externalVsCodeInstallationDir = vscode.extensions.getExtension("openmainframeproject.cobol-check-extension").extensionPath;
let configPath = appendPath(externalVsCodeInstallationDir, 'Cobol-check/config.properties');
let cobolCheckJarPath = appendPath(externalVsCodeInstallationDir, 'Cobol-check/bin/cobol-check-0.2.10.jar');
let cobolCheckJarPath = appendPath(externalVsCodeInstallationDir, 'Cobol-check/bin/cobol-check-0.2.11.jar');



Expand Down

0 comments on commit 312dc67

Please sign in to comment.