Skip to content

Commit

Permalink
change to inline expansion.
Browse files Browse the repository at this point in the history
Remove commenting out of linkage, replaced with new issue
Fix SQLCA.cpy to not use binary-long binary-short

Signed-off-by: Rune Christensen <ruc@bankdata.dk>
  • Loading branch information
Rune-Christensen authored and Rune Christensen committed Aug 8, 2023
1 parent 2f04d4e commit 9709307
Show file tree
Hide file tree
Showing 17 changed files with 226 additions and 134 deletions.
2 changes: 1 addition & 1 deletion config.properties
Original file line number Diff line number Diff line change
Expand Up @@ -147,7 +147,7 @@ application.source.filename.suffix = CBL,cbl,COB,cob
# If application copybook filenames have a suffix, specify it here without the period or dot
# e.g. application.copybook.filename.suffix = CBL
#---------------------------------------------------------------------------------------------------------------------
application.copybook.filename.suffix = CBL,cbl,COB,cob,cpy
application.copybook.filename.suffix = CBL,cbl,COB,cob,CPY,cpy

#---------------------------------------------------------------------------------------------------------------------
# Optional override of system default Locale for log messages and exception messages.
Expand Down
2 changes: 1 addition & 1 deletion gradle/wrapper/gradle-wrapper.properties
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
distributionBase=GRADLE_USER_HOME
distributionPath=wrapper/dists
distributionUrl=https\://services.gradle.org/distributions/gradle-6.7.1-all.zip
distributionUrl=https\://services.gradle.org/distributions/gradle-6.9.4-all.zip
zipStoreBase=GRADLE_USER_HOME
zipStorePath=wrapper/dists
11 changes: 5 additions & 6 deletions src/main/cobol/DB2PROG.cbl
Original file line number Diff line number Diff line change
Expand Up @@ -9,16 +9,15 @@
DATA DIVISION.
WORKING-STORAGE SECTION.

EXEC SQL INCLUDE SQLCA END-EXEC.
EXEC SQL INCLUDE TEXEM END-EXEC.

01 FILLER.
05 WS-FIELD-1 PIC X(80).
05 ws-Field-2 PIC X(80).


EXEC SQL INCLUDE SQLCA END-EXEC.
EXEC SQL INCLUDE TEXEM END-EXEC.

EXEC SQL
DECLARE NAME-CUR CURSOR FOR
EXEC SQL
DECLARE NAME-CUR CURSOR FOR
SELECT FIRST_NAME, LAST_NAME FROM TEXEM
END-EXEC.

Expand Down
8 changes: 4 additions & 4 deletions src/main/cobol/copy/SQLCA.cpy
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
01 SQLCA.
03 SQLCAID PIC X(8) VALUE "SQLCA ".
03 SQLCABC USAGE BINARY-LONG VALUE 136.
03 SQLCODE USAGE BINARY-LONG VALUE 0.
03 SQLCABC PIC S9(9) USAGE BINARY VALUE 136.
03 SQLCODE PIC S9(9) USAGE BINARY VALUE 0.
03 SQLERRM.
05 SQLERRML USAGE BINARY-SHORT.
05 SQLERRML PIC S9(4) USAGE BINARY.
05 SQLERRMC PIC X(70).
03 SQLERRP PIC X(8).
03 SQLERRD USAGE BINARY-LONG OCCURS 6.
03 SQLERRD PIC S9(9) USAGE BINARY OCCURS 6.
03 SQLWARN.
05 SQLWARN0 PIC X.
05 SQLWARN1 PIC X.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -141,7 +141,7 @@ public boolean shouldCurrentLineBeStubbed() throws IOException {
return true;
}
}
if (reader.getState().isFlagSetFor(Constants.WORKING_STORAGE_SECTION)||reader.getState().isFlagSetFor(Constants.LINKAGE_SECTION)) {
if (reader.getState().isFlagSetFor(Constants.WORKING_STORAGE_SECTION)) {
return Interpreter.shouldLineBeStubbed(reader.getCurrentLine(), reader.getState());
}
return false;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ public class Config {
public static final String LOCALE_VARIANT_CONFIG_KEY = "locale.variant";
public static final String DEFAULT_LOCALE_CONFIG_KEY = "default.locale";
public static final String RUN_GENERATED_TESTS_CONFIG_KEY = "cobolcheck.test.run";
public static final String RUN_GENERATED_TESTS_DEAFAULT = "true";
public static final String RUN_GENERATED_TESTS_DEFAULT = "true";
public static final String RESOLVED_APPLICATION_SOURCE_FILENAME_SUFFIX = "resolved.application.source.filename.suffix";
public static final String APPLICATION_SOURCE_FILENAME_SUFFIX = "application.source.filename.suffix";
public static final String RESOLVED_APPLICATION_COPYBOOK_FILENAME_SUFFIX = "resolved.application.copybook.filename.suffix";
Expand Down Expand Up @@ -278,7 +278,7 @@ public static DataTransferObjectStyle getTestResultFormatStyle() {
}

public static boolean getRunGeneratedTest() {
String value = settings.getProperty(RUN_GENERATED_TESTS_CONFIG_KEY, RUN_GENERATED_TESTS_DEAFAULT);
String value = settings.getProperty(RUN_GENERATED_TESTS_CONFIG_KEY, RUN_GENERATED_TESTS_DEFAULT);
return Boolean.parseBoolean(value.trim());
}
private static String sourceFolderContext = null;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -254,9 +254,6 @@ public static boolean shouldLineBeStubbed(CobolLine line, State state) {
if (line.containsToken(Constants.EXEC_SQL_TOKEN) || line.containsToken(Constants.INCLUDE) || line.containsToken(Constants.END_EXEC_TOKEN))
return true;
}
if (line.containsToken(Constants.LINKAGE_SECTION)) {
return true;
}
return false;
}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -126,8 +126,6 @@ private void processingBeforeEchoingSourceLineToOutput() throws IOException {
workingStorageHasEnded = true;
}
if (interpreter.didLineJustEnter(Constants.PROCEDURE_DIVISION) && interpreter.currentLineContains(Constants.PROCEDURE_DIVISION)){
if (!interpreter.getFileSectionStatements().isEmpty())
writerController.writeLines(interpreter.getFileSectionStatements());
writerController.stopStoringLines();
testSuiteParserController.parseTestSuites(interpreter.getNumericFields());
writerController.writeLines(testSuiteParserController.getWorkingStorageMockCode());
Expand Down Expand Up @@ -168,8 +166,11 @@ private void writeToSource(String sourceLine) throws IOException {
}
else {
if (interpreter.shouldCurrentLineBeStubbed()) {
if(interpreter.isReading(Constants.WORKING_STORAGE_SECTION))
if(interpreter.isReading(Constants.WORKING_STORAGE_SECTION)) {
writerController.writeStubbedLine(interpreter.getCurrentLineAsStatement().getUnNumberedString());
if (!interpreter.getFileSectionStatements().isEmpty())
writerController.writeLines(interpreter.getFileSectionStatements());
}
else
writerController.writeStubbedLine(sourceLine);
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ public void it_can_find_the_copybooks_for_cobolcheck_based_on_config_settings()

private Path findFileNamed(String filename) {
String resourcesDirectory = Config.getString("resources.directory");
String packagePathSegment = "com/neopragma/cobolcheck";
String packagePathSegment = "org/openmainframeproject/cobolcheck";
String copybookPathSegment = Config.getString("cobolcheck.copybook.directory");
return new File(
resourcesDirectory + Constants.FILE_SEPARATOR
Expand Down Expand Up @@ -102,7 +102,7 @@ public void it_returns_empty_string_when_application_copybook_filenames_have_no_
@Test
public void it_returns_list_of_specified_application_copybook_filename_suffixes() {
Config.load("testconfig.properties");
List<String> expected = new ArrayList(Arrays.asList( ".CBL", ".cbl", ".COB", ".cob" ));
List<String> expected = new ArrayList(Arrays.asList( ".CBL", ".cbl", ".COB", ".cob", ".CPY", ".cpy" ));
assertEquals(expected, Config.getCopybookFilenameSuffixes());
}
}
145 changes: 145 additions & 0 deletions src/test/java/org/openmainframeproject/cobolcheck/ExpanderTest.java
Original file line number Diff line number Diff line change
@@ -0,0 +1,145 @@
package org.openmainframeproject.cobolcheck;

import org.junit.jupiter.api.BeforeAll;
import org.junit.jupiter.api.BeforeEach;
import org.junit.jupiter.api.Test;
import org.mockito.Mockito;
import org.openmainframeproject.cobolcheck.features.interpreter.InterpreterController;
import org.openmainframeproject.cobolcheck.features.testSuiteParser.TestSuiteParserController;
import org.openmainframeproject.cobolcheck.features.writer.CobolWriter;
import org.openmainframeproject.cobolcheck.features.writer.WriterController;
import org.openmainframeproject.cobolcheck.services.Config;
import org.openmainframeproject.cobolcheck.services.Constants;
import org.openmainframeproject.cobolcheck.services.cobolLogic.Interpreter;
import org.openmainframeproject.cobolcheck.testhelpers.Utilities;
import org.openmainframeproject.cobolcheck.workers.Generator;

import java.io.BufferedReader;
import java.io.IOException;
import java.io.StringWriter;
import java.io.Writer;
import java.util.Arrays;
import java.util.List;

import static org.junit.jupiter.api.Assertions.assertEquals;

public class ExpanderTest {

private Generator generator;
private TestSuiteParserController testSuiteParserController;
private BufferedReader mockedParserReader;
private InterpreterController interpreterController;
private BufferedReader mockedInterpreterReader;
private Interpreter interpreter;
private CobolWriter cobolWriter;
private WriterController writerController;
private Writer writer;

private List<String> boilerPLateWS;
private List<String> boilerPLateDP;
List<String> boilerPlateTags = Arrays.asList("* CCHECKWS.CPY", "* CCHECKPARAGRAPHSPD.CPY", "* CCHECKRESULTPD.CPY");

@BeforeAll
static void oneTimeSetup() {
Config.load("testconfig.properties");
}

@BeforeEach
void commonSetup() throws IOException {
mockedInterpreterReader = Mockito.mock(BufferedReader.class);
interpreterController = new InterpreterController(mockedInterpreterReader);

writer = new StringWriter();
cobolWriter = new CobolWriter(writer);
writerController = new WriterController(cobolWriter);

mockedParserReader = Mockito.mock(BufferedReader.class);
testSuiteParserController = new TestSuiteParserController(mockedParserReader);

if (boilerPLateWS == null){
boilerPLateWS = testSuiteParserController.getBoilerplateCodeFromCopybooks("CCHECKWS.CPY");
boilerPLateDP = testSuiteParserController.getBoilerplateCodeFromCopybooks("CCHECKPARAGRAPHSPD.CPY");
}
}

@Test
public void it_inserts_a_mock_correctly() throws IOException {
String s1 = " WORKING-STORAGE SECTION.";
String s2 = " EXEC SQL INCLUDE TEXEM END-EXEC.";
String s3 = " 01 FILLER.";
String s4 = " 05 WS-FIELD-1 PIC X(80).";
String s5 = " 05 ws-Field-2 PIC X(80).";
String s6 = " PROCEDURE DIVISION.";
String s7 = " 000-START SECTION.";
String s8 = " MOVE \"Value1\" to WS-FIELD-1";
String s9 = " EXIT SECTION";
String s10 = " .";

String t1 = " TestSuite \"Basic test\"";
String t2 = " PERFORM 000-START";
String t3 = " EXPECT WS-FIELD-1 TO BE \"Value1\"";

Mockito.when(mockedInterpreterReader.readLine()).thenReturn(s1, s2, s3, s4, s5, s6, s7, s8, s9, s10, null);
Mockito.when(mockedParserReader.readLine()).thenReturn(t1, t2, t3, null);

generator = new Generator(interpreterController, writerController, testSuiteParserController);

List<String> actual = Utilities.getTrimmedList(Utilities.removeBoilerPlateCode(writer.toString(), boilerPlateTags));

assertEquals(Utilities.getTrimmedList(expected1), actual);
}

private String expected1 =
" WORKING-STORAGE SECTION. " + Constants.NEWLINE +
" *EXEC SQL INCLUDE TEXEM END-EXEC. " + Constants.NEWLINE +
" 01 TEXEM. " + Constants.NEWLINE +
" 10 FIRST-NAME PIC X(10). " + Constants.NEWLINE +
" 10 LAST-NAME PIC X(10). " + Constants.NEWLINE +
" 10 TMS-CREA PIC X(26). " + Constants.NEWLINE +
" 01 FILLER. " + Constants.NEWLINE +
" 05 WS-FIELD-1 PIC X(80). " + Constants.NEWLINE +
" 05 ws-Field-2 PIC X(80). " + Constants.NEWLINE +
" PROCEDURE DIVISION. " + Constants.NEWLINE +
" PERFORM UT-INITIALIZE " + Constants.NEWLINE +
" *============= \"Basic test\" =============* " + Constants.NEWLINE +
" DISPLAY \"TESTSUITE:\" " + Constants.NEWLINE +
" DISPLAY \"Basic test\" " + Constants.NEWLINE +
" MOVE \"Basic test\" " + Constants.NEWLINE +
" TO UT-TEST-SUITE-NAME " + Constants.NEWLINE +
" PERFORM 000-START " + Constants.NEWLINE +
" ADD 1 TO UT-TEST-CASE-COUNT " + Constants.NEWLINE +
" SET UT-NORMAL-COMPARE TO TRUE " + Constants.NEWLINE +
" SET UT-ALPHANUMERIC-COMPARE TO TRUE " + Constants.NEWLINE +
" MOVE WS-FIELD-1 TO UT-ACTUAL " + Constants.NEWLINE +
" MOVE \"Value1\" " + Constants.NEWLINE +
" TO UT-EXPECTED " + Constants.NEWLINE +
" SET UT-RELATION-EQ TO TRUE " + Constants.NEWLINE +
" PERFORM UT-CHECK-EXPECTATION " + Constants.NEWLINE +
" UT-BEFORE-EACH. " + Constants.NEWLINE +
" ***************************************************************** " + Constants.NEWLINE +
" *This is performed before each Test Case " + Constants.NEWLINE +
" ***************************************************************** " + Constants.NEWLINE +
" CONTINUE " + Constants.NEWLINE +
" . " + Constants.NEWLINE +
" " + Constants.NEWLINE +
" UT-AFTER-EACH. " + Constants.NEWLINE +
" ***************************************************************** " + Constants.NEWLINE +
" *This is performed after each Test Case " + Constants.NEWLINE +
" ***************************************************************** " + Constants.NEWLINE +
" CONTINUE " + Constants.NEWLINE +
" . " + Constants.NEWLINE +
" " + Constants.NEWLINE +
" UT-INITIALIZE-MOCK-COUNT. " + Constants.NEWLINE +
" ***************************************************************** " + Constants.NEWLINE +
" *Sets all global mock counters and expected count to 0 " + Constants.NEWLINE +
" ***************************************************************** " + Constants.NEWLINE +
" CONTINUE " + Constants.NEWLINE +
" . " + Constants.NEWLINE +
" " + Constants.NEWLINE +
" 000-START SECTION. " + Constants.NEWLINE +
" MOVE \"Value1\" to WS-FIELD-1 " + Constants.NEWLINE +
" EXIT SECTION " + Constants.NEWLINE +
" . " + Constants.NEWLINE;
}


Original file line number Diff line number Diff line change
Expand Up @@ -977,7 +977,7 @@ public void it_stubs_linkage_line() throws IOException {
while (currentLine != null){
currentLine = interpreterController.interpretNextLine();
if (currentLine != null && currentLine.contains("LINKAGE SECTION.")) {
assertTrue(interpreterController.shouldCurrentLineBeStubbed());
assertFalse(interpreterController.shouldCurrentLineBeStubbed());
testsRan = true;
}
}
Expand Down
Loading

0 comments on commit 9709307

Please sign in to comment.