Skip to content

Commit

Permalink
Merge pull request #303 from openmainframeproject/174-mocked-sections…
Browse files Browse the repository at this point in the history
…-and-paragraphs-cannot-handle-periods-in-bodies

174 mocked sections and paragraphs cannot handle periods in bodies
  • Loading branch information
issacto authored Aug 11, 2023
2 parents 847d2c4 + a7f1e96 commit 2531970
Show file tree
Hide file tree
Showing 14 changed files with 416 additions and 56 deletions.
22 changes: 22 additions & 0 deletions src/main/cobol/TESTNESTED.CBL
Original file line number Diff line number Diff line change
@@ -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
.
Original file line number Diff line number Diff line change
Expand Up @@ -284,5 +284,4 @@ boolean isFlagSet(String partOfProgram){
return state.getFlags().get(partOfProgram).isSet();
}


}
Original file line number Diff line number Diff line change
Expand Up @@ -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;
Expand All @@ -25,6 +26,8 @@ public class InterpreterController {
private List<String> possibleMockArgs;
private boolean insideSectionOrParagraphMockBody;
private TreeMap<Integer,String> currentDataStructure;
private final String stubTag;
private SectionOrParagraph sectionOrParagraph;

public InterpreterController(BufferedReader sourceReader) {
if (sourceReader == null) {
Expand All @@ -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
Expand Down Expand Up @@ -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();
}

Expand Down Expand Up @@ -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)){
Expand Down Expand Up @@ -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);
}
}
}

Expand Down Expand Up @@ -502,4 +506,30 @@ private void resetPossibleMockValues(){
possibleMockIdentifier = null;
possibleMockType = null;
}

public List<String> 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<String> lines){
for (String line : lines){
sectionOrParagraph.addLine(line);
}
}


}
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
package org.openmainframeproject.cobolcheck.features.interpreter;

import java.util.ArrayList;
import java.util.List;

public class SectionOrParagraph {

private List<String> lines;

public SectionOrParagraph(){
lines = new ArrayList<>();
}

void addLine(String line){
lines.add(line);
}

List<String> getLines(){
return lines;
}

void removeLines(){
lines.clear();
}
}
Original file line number Diff line number Diff line change
@@ -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 = " .";

Expand Down Expand Up @@ -72,4 +74,18 @@ static void addStartAndEndTags(List<String> lines){
if (!getInjectEndTagComment().isEmpty())
lines.add(getInjectEndTagComment());
}

static List<String> generateWhenOtherLines(String identifier, String type, List<String> commentLines, List<String> bodyLines){
List<String> 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;
}

}
Original file line number Diff line number Diff line change
Expand Up @@ -165,4 +165,5 @@ private String getArgumentText(){
}
return combinedArgs.substring(0, combinedArgs.length() - 2);
}

}
Original file line number Diff line number Diff line change
Expand Up @@ -156,4 +156,6 @@ private List<String> generateParagraphsForMock(Mock mock, boolean withComment){
body.addAll(mock.getLines());
return CobolGenerator.generateParagraphLines(mock.getGeneratedMockIdentifier(), comments, body);
}


}
Original file line number Diff line number Diff line change
Expand Up @@ -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";
Expand Down Expand Up @@ -1159,4 +1160,15 @@ public String getCobolStatement() {
public String getCurrentFieldName() {
return currentFieldName;
}

public WhenOther getWhenOtherSectionOrParagraph(String type, List<String> 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;

}

}
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ public class TestSuiteParserController {
private BeforeAfterRepo beforeAfterRepo;
private MockGenerator mockGenerator;
private BufferedReader testSuiteReader;
private WhenOtherGenerator whenOtherGenerator;

private TestSuiteErrorLog testSuiteErrorLog;

Expand Down Expand Up @@ -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
Expand All @@ -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() {
Expand Down Expand Up @@ -313,4 +316,17 @@ public void closeTestSuiteReader(){
public void prepareNextParse() {
Config.setDecimalPointIsCommaFromFile();
}

public List<String> generateWhenOtherSectionOrParagraph(String type, List<String> sectionOrParagraphlines, String sourceLine, String identifier, boolean withComments) throws IOException{
List<String> 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;
}


}
Original file line number Diff line number Diff line change
@@ -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<String> 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<String> lines) {
this.lines.addAll(lines);
}

public void setType(String type) {
this.type = type;
}

public String getType() {
return this.type;
}

public List<String> getLines() {
return this.lines;
}

public void setIdentifier(String identifier) {
this.identifier = identifier;
}


public List<String> getCommentText(){
List<String> newLines = new ArrayList<>();
newLines.add(" *****************************************************************");
newLines.add( "WhenOther of: " + type + ": " + identifier);
newLines.add(" *****************************************************************");
return newLines;

}

}
Original file line number Diff line number Diff line change
@@ -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<String> generateWhenOther(WhenOther whenOther, boolean withComments){
List<String> lines = new ArrayList<>();
lines.addAll(CobolGenerator.generateCommentBlock("WhenOther Paragraph or Section called"));
lines.addAll(generateParagraphsForWhenOther(whenOther, withComments));
lines.add("");
return lines;
}

private List<String> generateParagraphsForWhenOther(WhenOther whenOther, boolean withComments){
List<String> comments = new ArrayList<>();
if (withComments){
for (String line : whenOther.getCommentText()){
comments.add(StringHelper.commentOutLine(line));
}
}
List<String> body = new ArrayList<>();
body.addAll(whenOther.getLines());
return CobolGenerator.generateWhenOtherLines(whenOther.getGeneratedWhenOtherIdentifier(), whenOther.getType(), comments, body);
}


}
Loading

0 comments on commit 2531970

Please sign in to comment.