diff --git a/src/main/cobol/TESTNESTED.CBL b/src/main/cobol/TESTNESTED.CBL new file mode 100644 index 00000000..df0c8215 --- /dev/null +++ b/src/main/cobol/TESTNESTED.CBL @@ -0,0 +1,22 @@ + IDENTIFICATION DIVISION. + PROGRAM-ID. TESTNESTED. + ENVIRONMENT DIVISION. + INPUT-OUTPUT SECTION. + FILE-CONTROL. + DATA DIVISION. + + WORKING-STORAGE SECTION. + 01 FILLER. + 05 ONE-DIGIT PIC X(80). + + PROCEDURE DIVISION. + MOCK-SECTION-WITH-ERROR SECTION . + EVALUATE TRUE + WHEN ONE-DIGIT = 1 + MOVE 2 TO ONE-DIGIT + WHEN OTHER + MOVE 5 TO ONE-DIGIT + END-EVALUATE. + MOVE 9 TO ONE-DIGIT + EXIT SECTION + . diff --git a/src/main/java/org/openmainframeproject/cobolcheck/features/interpreter/CobolReader.java b/src/main/java/org/openmainframeproject/cobolcheck/features/interpreter/CobolReader.java index 5ed7ccea..fee1ec4a 100644 --- a/src/main/java/org/openmainframeproject/cobolcheck/features/interpreter/CobolReader.java +++ b/src/main/java/org/openmainframeproject/cobolcheck/features/interpreter/CobolReader.java @@ -284,5 +284,4 @@ boolean isFlagSet(String partOfProgram){ return state.getFlags().get(partOfProgram).isSet(); } - } diff --git a/src/main/java/org/openmainframeproject/cobolcheck/features/interpreter/InterpreterController.java b/src/main/java/org/openmainframeproject/cobolcheck/features/interpreter/InterpreterController.java index 91988963..ab4db17b 100644 --- a/src/main/java/org/openmainframeproject/cobolcheck/features/interpreter/InterpreterController.java +++ b/src/main/java/org/openmainframeproject/cobolcheck/features/interpreter/InterpreterController.java @@ -4,6 +4,7 @@ import org.openmainframeproject.cobolcheck.exceptions.PossibleInternalLogicErrorException; import org.openmainframeproject.cobolcheck.services.Config; import org.openmainframeproject.cobolcheck.services.Messages; +import org.openmainframeproject.cobolcheck.services.StringHelper; import org.openmainframeproject.cobolcheck.services.Constants; import org.openmainframeproject.cobolcheck.services.cobolLogic.*; import org.openmainframeproject.cobolcheck.services.log.Log; @@ -25,6 +26,8 @@ public class InterpreterController { private List possibleMockArgs; private boolean insideSectionOrParagraphMockBody; private TreeMap currentDataStructure; + private final String stubTag; + private SectionOrParagraph sectionOrParagraph; public InterpreterController(BufferedReader sourceReader) { if (sourceReader == null) { @@ -36,6 +39,8 @@ public InterpreterController(BufferedReader sourceReader) { numericFields = new NumericFields(); tokenExtractor = new StringTokenizerExtractor(); currentDataStructure = new TreeMap<>(); + stubTag = Config.getStubTag(); + sectionOrParagraph = new SectionOrParagraph(); } //Getters for lists of specific source lines @@ -177,8 +182,6 @@ public String interpretNextLine(){ } catch (IOException ex){ throw new CobolSourceCouldNotBeReadException(ex); } - - //Current line might change from when it was originally read return reader.getCurrentLine().getUnNumberedString(); } @@ -209,7 +212,7 @@ private void updateDependencies(CobolLine line) throws IOException { if (Interpreter.shouldLineBeReadAsStatement(line, reader.getState())){ currentStatement = reader.readTillEndOfStatement(); } else { - currentStatement.add(line); + currentStatement.add(line); } if (reader.isFlagSet(Constants.SPECIAL_NAMES_PARAGRAPH)){ @@ -284,8 +287,9 @@ private void updatePossibleMock(CobolLine line) throws IOException { private void updatePossibleStub(CobolLine line) throws IOException { if (Interpreter.shouldLineBeStubbed(line, reader.getState())) { String stubEndToken = Interpreter.getStubEndToken(line, reader.getState()); - if (stubEndToken != null) + if (stubEndToken != null) { reader.readTillHitToken(stubEndToken, false); + } } } @@ -502,4 +506,30 @@ private void resetPossibleMockValues(){ possibleMockIdentifier = null; possibleMockType = null; } + + public List getSectionOrParagraphLines(){ + return sectionOrParagraph.getLines(); + } + + public void removeSectionOrParagraphLines(){ + sectionOrParagraph.removeLines(); + } + + public void addSectionOrParagraphLine(){ + if(Interpreter.shouldLineBeStubbed(reader.getCurrentLine(), reader.getState())) + sectionOrParagraph.addLine(StringHelper.stubLine(reader.getCurrentLine().getUnNumberedString(), stubTag)); + else sectionOrParagraph.addLine(reader.getCurrentLine().getUnNumberedString()); + } + + public void addSectionOrParagraphLine(String line){ + sectionOrParagraph.addLine(line); + } + + public void addSectionOrParagraphLines(List lines){ + for (String line : lines){ + sectionOrParagraph.addLine(line); + } + } + + } diff --git a/src/main/java/org/openmainframeproject/cobolcheck/features/interpreter/SectionOrParagraph.java b/src/main/java/org/openmainframeproject/cobolcheck/features/interpreter/SectionOrParagraph.java new file mode 100644 index 00000000..df74a952 --- /dev/null +++ b/src/main/java/org/openmainframeproject/cobolcheck/features/interpreter/SectionOrParagraph.java @@ -0,0 +1,25 @@ +package org.openmainframeproject.cobolcheck.features.interpreter; + +import java.util.ArrayList; +import java.util.List; + +public class SectionOrParagraph { + + private List lines; + + public SectionOrParagraph(){ + lines = new ArrayList<>(); + } + + void addLine(String line){ + lines.add(line); + } + + List getLines(){ + return lines; + } + + void removeLines(){ + lines.clear(); + } +} diff --git a/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/CobolGenerator.java b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/CobolGenerator.java index 3d1eaeb7..5c266f2f 100644 --- a/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/CobolGenerator.java +++ b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/CobolGenerator.java @@ -1,13 +1,15 @@ package org.openmainframeproject.cobolcheck.features.testSuiteParser; import org.openmainframeproject.cobolcheck.services.Config; +import org.openmainframeproject.cobolcheck.services.Constants; import org.openmainframeproject.cobolcheck.services.StringHelper; import java.util.ArrayList; import java.util.List; public class CobolGenerator { - private final static String SECTION_HEADER_FORMAT = " SECTION %s."; + private final static String SECTION_HEADER_FORMAT = " SECTION %s."; + private final static String WHEN_OTHER_SECTION_HEADER_FORMAT = " %s SECTION."; private final static String PARAGRAPH_HEADER_FORMAT = " %s."; private final static String ENDING_PERIOD = " ."; @@ -72,4 +74,18 @@ static void addStartAndEndTags(List lines){ if (!getInjectEndTagComment().isEmpty()) lines.add(getInjectEndTagComment()); } + + static List generateWhenOtherLines(String identifier, String type, List commentLines, List bodyLines){ + List lines = new ArrayList<>(); + if(type.equals(Constants.SECTION_TOKEN)) + lines.add(String.format(WHEN_OTHER_SECTION_HEADER_FORMAT, identifier)); + else lines.add(String.format(PARAGRAPH_HEADER_FORMAT, identifier)); + if (commentLines != null) + lines.addAll(commentLines); + if (bodyLines != null) + lines.addAll(bodyLines); + lines.add(ENDING_PERIOD); + return lines; + } + } diff --git a/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/Mock.java b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/Mock.java index 8f1a70db..ba5717d0 100644 --- a/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/Mock.java +++ b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/Mock.java @@ -165,4 +165,5 @@ private String getArgumentText(){ } return combinedArgs.substring(0, combinedArgs.length() - 2); } + } diff --git a/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/MockGenerator.java b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/MockGenerator.java index 898b6003..eb188db6 100644 --- a/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/MockGenerator.java +++ b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/MockGenerator.java @@ -156,4 +156,6 @@ private List generateParagraphsForMock(Mock mock, boolean withComment){ body.addAll(mock.getLines()); return CobolGenerator.generateParagraphLines(mock.getGeneratedMockIdentifier(), comments, body); } + + } diff --git a/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/TestSuiteParser.java b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/TestSuiteParser.java index 6b8ae6c9..278d8504 100644 --- a/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/TestSuiteParser.java +++ b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/TestSuiteParser.java @@ -75,6 +75,7 @@ public class TestSuiteParser { private String currentTestCaseName = Constants.EMPTY_STRING; private int testCaseNumber = 0; private boolean expectNumericCompare; + private int whenOtherNumber=0; // Lines inserted into the test program private static final String COBOL_PERFORM_INITIALIZE = " PERFORM %sINITIALIZE"; @@ -1159,4 +1160,15 @@ public String getCobolStatement() { public String getCurrentFieldName() { return currentFieldName; } + + public WhenOther getWhenOtherSectionOrParagraph(String type, List lines, String itdentifier, boolean withComments){ + WhenOther whenOther = new WhenOther(testSuiteNumber, testCaseNumber, whenOtherNumber); + whenOther.addLines(lines); + whenOther.setType(type); + whenOther.setIdentifier(itdentifier); + whenOtherNumber += 1; + return whenOther; + + } + } diff --git a/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/TestSuiteParserController.java b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/TestSuiteParserController.java index 8667db1b..60581522 100644 --- a/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/TestSuiteParserController.java +++ b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/TestSuiteParserController.java @@ -21,6 +21,7 @@ public class TestSuiteParserController { private BeforeAfterRepo beforeAfterRepo; private MockGenerator mockGenerator; private BufferedReader testSuiteReader; + private WhenOtherGenerator whenOtherGenerator; private TestSuiteErrorLog testSuiteErrorLog; @@ -54,6 +55,7 @@ public TestSuiteParserController(String testFileNames) { testSuiteParser = new TestSuiteParser(new KeywordExtractor(), mockRepository, beforeAfterRepo, testSuiteErrorLog); mockGenerator = new MockGenerator(); testCodePrefix = Config.getTestCodePrefix(); + whenOtherGenerator = new WhenOtherGenerator(); } //Used for testing only @@ -65,6 +67,7 @@ public TestSuiteParserController(BufferedReader reader) { testSuiteParser = new TestSuiteParser(new KeywordExtractor(), mockRepository, beforeAfterRepo, testSuiteErrorLog); mockGenerator = new MockGenerator(); testCodePrefix = Config.getString(Constants.COBOLCHECK_PREFIX_CONFIG_KEY, Constants.DEFAULT_COBOLCHECK_PREFIX); + whenOtherGenerator = new WhenOtherGenerator(); } public boolean hasWorkingStorageTestCodeBeenInserted() { @@ -313,4 +316,17 @@ public void closeTestSuiteReader(){ public void prepareNextParse() { Config.setDecimalPointIsCommaFromFile(); } + + public List generateWhenOtherSectionOrParagraph(String type, List sectionOrParagraphlines, String sourceLine, String identifier, boolean withComments) throws IOException{ + List lines = new ArrayList<>(); + WhenOther whenOther = testSuiteParser.getWhenOtherSectionOrParagraph(type, sectionOrParagraphlines, identifier, true); + lines.add(whenOtherGenerator.generateWhenOtherCall(whenOther)); + lines.addAll(this.getEndEvaluateLine()); + lines.add(sourceLine); + lines.add(""); + lines.addAll(whenOtherGenerator.generateWhenOther(whenOther, withComments)); + return lines; + } + + } diff --git a/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/WhenOther.java b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/WhenOther.java new file mode 100644 index 00000000..7cdd58f8 --- /dev/null +++ b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/WhenOther.java @@ -0,0 +1,65 @@ +package org.openmainframeproject.cobolcheck.features.testSuiteParser; + + +import java.util.ArrayList; +import java.util.List; + +import org.openmainframeproject.cobolcheck.services.Config; +import org.openmainframeproject.cobolcheck.services.StringHelper; + +public class WhenOther { + + private String identifier; + private String type; + private List lines; + private int testSuiteNumber; + private int testCaseNumber; + private int mockNumber; + + + public WhenOther(int testSuiteNumber, int testCaseNumber, int mockNumber) { + this.testSuiteNumber = testSuiteNumber; + this.testCaseNumber = testCaseNumber; + this.mockNumber = mockNumber; + lines = new ArrayList<>(); + } + + public String getGeneratedWhenOtherIdentifier(){ + return Config.getTestCodePrefix() + getGeneratedWhenOtherIdentifierRoot(); + } + + public String getGeneratedWhenOtherIdentifierRoot(){ + return testSuiteNumber + "-" + testCaseNumber + "-" + mockNumber + "-WO"; + } + + public void addLines(List lines) { + this.lines.addAll(lines); + } + + public void setType(String type) { + this.type = type; + } + + public String getType() { + return this.type; + } + + public List getLines() { + return this.lines; + } + + public void setIdentifier(String identifier) { + this.identifier = identifier; + } + + + public List getCommentText(){ + List newLines = new ArrayList<>(); + newLines.add(" *****************************************************************"); + newLines.add( "WhenOther of: " + type + ": " + identifier); + newLines.add(" *****************************************************************"); + return newLines; + + } + +} diff --git a/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/WhenOtherGenerator.java b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/WhenOtherGenerator.java new file mode 100644 index 00000000..f00a7736 --- /dev/null +++ b/src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/WhenOtherGenerator.java @@ -0,0 +1,37 @@ +package org.openmainframeproject.cobolcheck.features.testSuiteParser; + +import java.util.ArrayList; +import java.util.List; + +import org.openmainframeproject.cobolcheck.services.StringHelper; + +public class WhenOtherGenerator { + private final String performFormat = " PERFORM %s"; + + + String generateWhenOtherCall(WhenOther whenOther) { + return String.format(performFormat, whenOther.getGeneratedWhenOtherIdentifier()); + } + + List generateWhenOther(WhenOther whenOther, boolean withComments){ + List lines = new ArrayList<>(); + lines.addAll(CobolGenerator.generateCommentBlock("WhenOther Paragraph or Section called")); + lines.addAll(generateParagraphsForWhenOther(whenOther, withComments)); + lines.add(""); + return lines; + } + + private List generateParagraphsForWhenOther(WhenOther whenOther, boolean withComments){ + List comments = new ArrayList<>(); + if (withComments){ + for (String line : whenOther.getCommentText()){ + comments.add(StringHelper.commentOutLine(line)); + } + } + List body = new ArrayList<>(); + body.addAll(whenOther.getLines()); + return CobolGenerator.generateWhenOtherLines(whenOther.getGeneratedWhenOtherIdentifier(), whenOther.getType(), comments, body); + } + + +} diff --git a/src/main/java/org/openmainframeproject/cobolcheck/workers/Generator.java b/src/main/java/org/openmainframeproject/cobolcheck/workers/Generator.java index c3b55297..ae633ab1 100644 --- a/src/main/java/org/openmainframeproject/cobolcheck/workers/Generator.java +++ b/src/main/java/org/openmainframeproject/cobolcheck/workers/Generator.java @@ -1,19 +1,24 @@ package org.openmainframeproject.cobolcheck.workers; +import java.io.BufferedReader; +import java.io.File; +import java.io.IOException; +import java.io.Reader; +import java.io.Writer; +import java.util.List; + import org.openmainframeproject.cobolcheck.exceptions.CobolSourceCouldNotBeReadException; import org.openmainframeproject.cobolcheck.exceptions.PossibleInternalLogicErrorException; import org.openmainframeproject.cobolcheck.features.interpreter.InterpreterController; +import org.openmainframeproject.cobolcheck.features.prepareMerge.PrepareMergeController; +import org.openmainframeproject.cobolcheck.features.testSuiteParser.Mock; import org.openmainframeproject.cobolcheck.features.testSuiteParser.TestSuiteParserController; import org.openmainframeproject.cobolcheck.features.writer.WriterController; -import org.openmainframeproject.cobolcheck.features.prepareMerge.PrepareMergeController; import org.openmainframeproject.cobolcheck.services.Constants; import org.openmainframeproject.cobolcheck.services.Messages; import org.openmainframeproject.cobolcheck.services.RunInfo; import org.openmainframeproject.cobolcheck.services.log.Log; -import java.io.*; -import java.util.*; - /** * This class merges a Test Suite (a text file) with the source of the Cobol program to be tested, * producing a Cobol program with the unit test cases embedded in it. @@ -29,6 +34,9 @@ public class Generator { private boolean workingStorageHasEnded; List matchingTestDirectories; + + private String currentIdentifier; + private String currentMockType; public Generator() { } @@ -40,7 +48,9 @@ public Generator(InterpreterController interpreter, WriterController writerContr this.interpreter = interpreter; this.writerController = writerController; this.testSuiteParserController = testSuiteParserController; + this.currentMockType=null; mergeTestSuite(); + } @@ -88,12 +98,9 @@ public void prepareAndRunMerge(String programName, String testFileNames) { private void mergeTestSuite() { String sourceLine; try { - while ((sourceLine = interpreter.interpretNextLine()) != null) { + while ((sourceLine = interpreter.interpretNextLine()) != null) { processingBeforeEchoingSourceLineToOutput(); - sourceLine = tryInsertEndEvaluateAtMockedCompomentEnd(sourceLine); - - writeToSource(sourceLine); - + echoingSourceLineToOutput(sourceLine); processingAfterEchoingSourceLineToOutput(); } testSuiteParserController.logUnusedMocks(); @@ -118,7 +125,6 @@ private void processingBeforeEchoingSourceLineToOutput() throws IOException { if (!workingStorageHasEnded && interpreter.isCurrentLineEndingWorkingStorageSection()) { if (!testSuiteParserController.hasWorkingStorageTestCodeBeenInserted()) { writerController.writeLine(testSuiteParserController.getWorkingStorageHeader()); - writerController.writeLines(testSuiteParserController.getWorkingStorageTestCode( interpreter.getFileSectionStatements())); } @@ -137,8 +143,10 @@ private String tryInsertEndEvaluateAtMockedCompomentEnd(String sourceLine) throw if (interpreter.isInsideSectionOrParagraphMockBody()){ if (interpreter.isCurrentLineEndingSectionOrParagraph()){ if (interpreter.canWriteEndEvaluateBeforeCurrentLine()){ + writeWhenOtherSectionOrParagraph(sourceLine); + interpreter.removeSectionOrParagraphLines(); interpreter.setInsideSectionOrParagraphMockBody(false); - writerController.writeLines(testSuiteParserController.getEndEvaluateLine()); + return ""; } else return sourceLine.replace(".", ""); @@ -197,9 +205,17 @@ private void processingAfterEchoingSourceLineToOutput() throws IOException { String type = interpreter.getPossibleMockType(); List arguments = interpreter.getPossibleMockArgs(); if (testSuiteParserController.mockExistsFor(identifier, type, arguments)){ - writerController.writeLines(testSuiteParserController.generateMockPerformCalls(identifier, type, arguments)); - if (type.equals(Constants.SECTION_TOKEN) || type.equals(Constants.PARAGRAPH_TOKEN)) + if(interpreter.isInsideSectionOrParagraphMockBody()){ + interpreter.addSectionOrParagraphLines(testSuiteParserController.generateMockPerformCalls(identifier, type, arguments)); + if (type.equals(Constants.CALL_TOKEN)){ + interpreter.addSectionOrParagraphLine(" CONTINUE"); + } + }else writerController.writeLines(testSuiteParserController.generateMockPerformCalls(identifier, type, arguments)); + if (type.equals(Constants.SECTION_TOKEN) || type.equals(Constants.PARAGRAPH_TOKEN)){ + this.currentIdentifier = identifier; + this.currentMockType=interpreter.getPossibleMockType(); interpreter.setInsideSectionOrParagraphMockBody(true); + } } } } @@ -210,4 +226,24 @@ private void closeReadersAndWriters(String programName) { writerController.closeWriter(programName); } + private void writeWhenOtherSectionOrParagraph(String sourceLine) throws IOException{ + writerController.writeLines(testSuiteParserController.generateWhenOtherSectionOrParagraph(currentMockType, interpreter.getSectionOrParagraphLines(), sourceLine, currentIdentifier, true)); + } + + private void echoingSourceLineToOutput(String sourceLine){ + try{ + if(interpreter.isInsideSectionOrParagraphMockBody()){ + interpreter.addSectionOrParagraphLine(); + } + sourceLine = tryInsertEndEvaluateAtMockedCompomentEnd(sourceLine); + if(!interpreter.isInsideSectionOrParagraphMockBody()){ + writeToSource(sourceLine); + } + } catch (IOException ioEx) { + throw new CobolSourceCouldNotBeReadException(ioEx); + } + catch (Exception ex) { + throw new PossibleInternalLogicErrorException(ex); + } + } } diff --git a/src/test/cobol/TESTNESTED/TestNested.cut b/src/test/cobol/TESTNESTED/TestNested.cut new file mode 100644 index 00000000..f91e585a --- /dev/null +++ b/src/test/cobol/TESTNESTED/TestNested.cut @@ -0,0 +1,10 @@ + TestSuite "Test Nested" + + TestCase "Test Nested" + MOVE 5 TO ONE-DIGIT + MOCK SECTION MOCK-SECTION-WITH-ERROR MOVE 3 TO ONE-DIGIT + END-MOCK + PERFORM MOCK-SECTION-WITH-ERROR + EXPECT ONE-DIGIT TO BE 3 + + diff --git a/src/test/java/org/openmainframeproject/cobolcheck/MockIT.java b/src/test/java/org/openmainframeproject/cobolcheck/MockIT.java index e6032d05..d0cf55b1 100644 --- a/src/test/java/org/openmainframeproject/cobolcheck/MockIT.java +++ b/src/test/java/org/openmainframeproject/cobolcheck/MockIT.java @@ -77,11 +77,11 @@ public void it_inserts_a_mock_correctly() throws IOException { Mockito.when(mockedInterpreterReader.readLine()).thenReturn(s1, s2, s3, s4, s5, s6, null); Mockito.when(mockedParserReader.readLine()).thenReturn(t1, t2, t3, t4, null); + generator = new Generator(interpreterController, writerController, testSuiteParserController); List actual = getTrimmedList(removeBoilerPlateCode(writer.toString(), boilerPlateTags)); - assertEquals(getTrimmedList(expected1), actual); } @@ -126,7 +126,6 @@ public void it_inserts_mocks_correctly_with_source_code_changing_code_style() th generator = new Generator(interpreterController, writerController, testSuiteParserController); List actual = getTrimmedList(removeBoilerPlateCode(writer.toString(), boilerPlateTags)); - assertEquals(getTrimmedList(expected2), actual); } @@ -353,10 +352,23 @@ private String removeBoilerPlateCode(String code, List boilerPlateTags){ " ALSO ANY " + Constants.NEWLINE + " PERFORM UT-1-0-1-MOCK " + Constants.NEWLINE + " WHEN OTHER " + Constants.NEWLINE + + " PERFORM UT-1-0-0-WO " + Constants.NEWLINE + + " END-EVALUATE " + Constants.NEWLINE + + " . " + Constants.NEWLINE + + " " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther Paragraph or Section called " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " UT-1-0-0-WO SECTION. " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther of: SECTION: 000-START " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + " MOVE \"Value1\" to VALUE-1 " + Constants.NEWLINE + " EXIT SECTION " + Constants.NEWLINE + - " END-EVALUATE " + Constants.NEWLINE + - " . " + Constants.NEWLINE; + " . " + Constants.NEWLINE+ + " . " + Constants.NEWLINE+ + " " + Constants.NEWLINE+ + " "+ Constants.NEWLINE; private String expected2 = " WORKING-STORAGE SECTION. " + Constants.NEWLINE + @@ -491,41 +503,80 @@ private String removeBoilerPlateCode(String code, List boilerPlateTags){ " 000-START SECTION. " + Constants.NEWLINE + " EVALUATE UT-TEST-SUITE-NAME " + Constants.NEWLINE + " ALSO UT-TEST-CASE-NAME " + Constants.NEWLINE + - " WHEN \"Mocking tests\" " + Constants.NEWLINE + - " ALSO \"Local mock overwrites global mock\" " + Constants.NEWLINE + + " WHEN \"Mocking tests\" " + Constants.NEWLINE + + " ALSO \"Local mock overwrites global mock\" " + Constants.NEWLINE + " PERFORM UT-1-1-1-MOCK " + Constants.NEWLINE + - " WHEN \"Mocking tests\" " + Constants.NEWLINE + - " ALSO \"Simply a test\" " + Constants.NEWLINE + - " PERFORM UT-1-2-1-MOCK " + Constants.NEWLINE + - " WHEN \"Mocking tests\" " + Constants.NEWLINE + - " ALSO ANY " + Constants.NEWLINE + - " PERFORM UT-1-0-1-MOCK " + Constants.NEWLINE + - " WHEN OTHER " + Constants.NEWLINE + + " WHEN \"Mocking tests\" " + Constants.NEWLINE + + " ALSO \"Simply a test\" " + Constants.NEWLINE + + " PERFORM UT-1-2-1-MOCK " + Constants.NEWLINE + + " WHEN \"Mocking tests\" " + Constants.NEWLINE + + " ALSO ANY " + Constants.NEWLINE + + " PERFORM UT-1-0-1-MOCK " + Constants.NEWLINE + + " WHEN OTHER " + Constants.NEWLINE + + " PERFORM UT-1-2-0-WO " + Constants.NEWLINE + + " END-EVALUATE " + Constants.NEWLINE + + " . " + Constants.NEWLINE + + " " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther Paragraph or Section called " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " UT-1-2-0-WO SECTION. " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther of: SECTION: 000-START " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + " MOVE \"Value1\" to VALUE-1 " + Constants.NEWLINE + - " EXIT SECTION " + Constants.NEWLINE + - " END-EVALUATE " + Constants.NEWLINE + - " . " + Constants.NEWLINE + + " EXIT SECTION. " + Constants.NEWLINE + + " . " + Constants.NEWLINE+ + " . " + Constants.NEWLINE+ + " " + Constants.NEWLINE+ + " " + Constants.NEWLINE+ " 100-WELCOME SECTION. " + Constants.NEWLINE + - " " + Constants.NEWLINE + + " " + Constants.NEWLINE+ " EVALUATE UT-TEST-SUITE-NAME " + Constants.NEWLINE + " ALSO UT-TEST-CASE-NAME " + Constants.NEWLINE + " WHEN \"Mocking tests\" " + Constants.NEWLINE + - " ALSO \"Simply a test\" " + Constants.NEWLINE + + " ALSO \"Simply a test\" " + Constants.NEWLINE + " PERFORM UT-1-2-2-MOCK " + Constants.NEWLINE + " WHEN OTHER " + Constants.NEWLINE + - " MOVE \"Hello\" to VALUE-1 " + Constants.NEWLINE + - " END-EVALUATE " + Constants.NEWLINE + + " PERFORM UT-1-2-1-WO " + Constants.NEWLINE + + " END-EVALUATE " + Constants.NEWLINE + + " . " + Constants.NEWLINE + + " " + Constants.NEWLINE+ + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther Paragraph or Section called " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " UT-1-2-1-WO SECTION. " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther of: SECTION: 100-WELCOME " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " MOVE \"Hello\" to VALUE-1. " + Constants.NEWLINE + + " . " + Constants.NEWLINE + " . " + Constants.NEWLINE + - " 200-GOODBYE SECTION . " + Constants.NEWLINE + + " " + Constants.NEWLINE+ + " " + Constants.NEWLINE+ + " 200-GOODBYE SECTION . " + Constants.NEWLINE + " EVALUATE UT-TEST-SUITE-NAME " + Constants.NEWLINE + " ALSO UT-TEST-CASE-NAME " + Constants.NEWLINE + " WHEN \"Mocking tests\" " + Constants.NEWLINE + - " ALSO \"Simply a test\" " + Constants.NEWLINE + + " ALSO \"Simply a test\" " + Constants.NEWLINE + " PERFORM UT-1-2-3-MOCK " + Constants.NEWLINE + " WHEN OTHER " + Constants.NEWLINE + - " MOVE \"Bye\" to VALUE-1 " + Constants.NEWLINE + - " END-EVALUATE " + Constants.NEWLINE + - " . " + Constants.NEWLINE; + " PERFORM UT-1-2-2-WO " + Constants.NEWLINE + + " END-EVALUATE " + Constants.NEWLINE + + " . " + Constants.NEWLINE + + " " + Constants.NEWLINE+ + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther Paragraph or Section called " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " UT-1-2-2-WO SECTION. " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther of: SECTION: 200-GOODBYE " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " MOVE \"Bye\" to VALUE-1 " + Constants.NEWLINE + + " . " + Constants.NEWLINE + + " . " + Constants.NEWLINE + + " " + Constants.NEWLINE+ + " " + Constants.NEWLINE; private String expected3 = " WORKING-STORAGE SECTION. " + Constants.NEWLINE + @@ -730,14 +781,27 @@ private String removeBoilerPlateCode(String code, List boilerPlateTags){ " 000-START SECTION. " + Constants.NEWLINE + " EVALUATE UT-TEST-SUITE-NAME " + Constants.NEWLINE + " ALSO UT-TEST-CASE-NAME " + Constants.NEWLINE + - " WHEN \"Mocking tests\" " + Constants.NEWLINE + - " ALSO \"Simply a test\" " + Constants.NEWLINE + + " WHEN \"Mocking tests\" " + Constants.NEWLINE + + " ALSO \"Simply a test\" " + Constants.NEWLINE + " PERFORM UT-1-2-1-MOCK " + Constants.NEWLINE + " WHEN OTHER " + Constants.NEWLINE + + " PERFORM UT-1-2-0-WO " + Constants.NEWLINE + + " END-EVALUATE " + Constants.NEWLINE + + " . " + Constants.NEWLINE + + " " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther Paragraph or Section called " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " UT-1-2-0-WO SECTION. " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther of: SECTION: 000-START " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + " MOVE \"Value1\" to VALUE-1 " + Constants.NEWLINE + - " EXIT SECTION " + Constants.NEWLINE + - " END-EVALUATE " + Constants.NEWLINE + - " . " + Constants.NEWLINE + + " EXIT SECTION. " + Constants.NEWLINE + + " . " + Constants.NEWLINE+ + " . " + Constants.NEWLINE + + " " + Constants.NEWLINE+ + " " + Constants.NEWLINE+ " 100-WELCOME SECTION. " + Constants.NEWLINE + " EVALUATE UT-TEST-SUITE-NAME " + Constants.NEWLINE + " ALSO UT-TEST-CASE-NAME " + Constants.NEWLINE + @@ -745,6 +809,17 @@ private String removeBoilerPlateCode(String code, List boilerPlateTags){ " ALSO ANY " + Constants.NEWLINE + " PERFORM UT-1-0-1-MOCK " + Constants.NEWLINE + " WHEN OTHER " + Constants.NEWLINE + + " PERFORM UT-1-2-1-WO " + Constants.NEWLINE + + " END-EVALUATE " + Constants.NEWLINE + + " . " + Constants.NEWLINE + + " " + Constants.NEWLINE+ + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther Paragraph or Section called " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " UT-1-2-1-WO SECTION. " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther of: SECTION: 100-WELCOME " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + " * CALL 'prog1' USING BY CONTENT VALUE-1, VALUE-2. " + Constants.NEWLINE + " EVALUATE UT-TEST-SUITE-NAME " + Constants.NEWLINE + " ALSO UT-TEST-CASE-NAME " + Constants.NEWLINE + @@ -752,10 +827,12 @@ private String removeBoilerPlateCode(String code, List boilerPlateTags){ " ALSO \"Simply a test\" " + Constants.NEWLINE + " PERFORM UT-1-2-2-MOCK " + Constants.NEWLINE + " END-EVALUATE " + Constants.NEWLINE + - " CONTINUE " + Constants.NEWLINE + - " MOVE \"Hello\" to VALUE-1 " + Constants.NEWLINE + - " END-EVALUATE " + Constants.NEWLINE + + " CONTINUE " + Constants.NEWLINE + + " MOVE \"Hello\" to VALUE-1. " + Constants.NEWLINE + " . " + Constants.NEWLINE + + " . " + Constants.NEWLINE + + " " + Constants.NEWLINE+ + " " + Constants.NEWLINE+ " 200-GOODBYE SECTION. " + Constants.NEWLINE + " EVALUATE UT-TEST-SUITE-NAME " + Constants.NEWLINE + " ALSO UT-TEST-CASE-NAME " + Constants.NEWLINE + @@ -766,9 +843,19 @@ private String removeBoilerPlateCode(String code, List boilerPlateTags){ " ALSO \"Simply a test\" " + Constants.NEWLINE + " PERFORM UT-1-2-3-MOCK " + Constants.NEWLINE + " WHEN OTHER " + Constants.NEWLINE + + " PERFORM UT-1-2-2-WO " + Constants.NEWLINE + + " END-EVALUATE " + Constants.NEWLINE + + " . " + Constants.NEWLINE + + " " + Constants.NEWLINE+ + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther Paragraph or Section called " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " UT-1-2-2-WO SECTION. " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + + " *WhenOther of: SECTION: 200-GOODBYE " + Constants.NEWLINE + + " ***************************************************************** " + Constants.NEWLINE + " MOVE \"Bye\" to VALUE-1 " + Constants.NEWLINE + " * CALL bogus USING VALUE-1 " + Constants.NEWLINE + - " CONTINUE " + Constants.NEWLINE + " " + Constants.NEWLINE + " * CALL 'prog2' USING VALUE-1 " + Constants.NEWLINE + " EVALUATE UT-TEST-SUITE-NAME " + Constants.NEWLINE + @@ -777,7 +864,7 @@ private String removeBoilerPlateCode(String code, List boilerPlateTags){ " ALSO ANY " + Constants.NEWLINE + " PERFORM UT-1-0-2-MOCK " + Constants.NEWLINE + " END-EVALUATE " + Constants.NEWLINE + - " CONTINUE " + Constants.NEWLINE + + " CONTINUE " + Constants.NEWLINE + " * CALL 'prog2' USING VALUE-1. " + Constants.NEWLINE + " EVALUATE UT-TEST-SUITE-NAME " + Constants.NEWLINE + " ALSO UT-TEST-CASE-NAME " + Constants.NEWLINE + @@ -785,9 +872,11 @@ private String removeBoilerPlateCode(String code, List boilerPlateTags){ " ALSO ANY " + Constants.NEWLINE + " PERFORM UT-1-0-2-MOCK " + Constants.NEWLINE + " END-EVALUATE " + Constants.NEWLINE + - " CONTINUE " + Constants.NEWLINE + - " END-EVALUATE " + Constants.NEWLINE + + " CONTINUE " + Constants.NEWLINE + " . " + Constants.NEWLINE + + " . " + Constants.NEWLINE + + " " + Constants.NEWLINE + + " " + Constants.NEWLINE + " * Ending with comment "; }