-
Notifications
You must be signed in to change notification settings - Fork 28
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Merge pull request #303 from openmainframeproject/174-mocked-sections…
…-and-paragraphs-cannot-handle-periods-in-bodies 174 mocked sections and paragraphs cannot handle periods in bodies
- Loading branch information
Showing
14 changed files
with
416 additions
and
56 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 | ||
. |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -284,5 +284,4 @@ boolean isFlagSet(String partOfProgram){ | |
return state.getFlags().get(partOfProgram).isSet(); | ||
} | ||
|
||
|
||
} |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
25 changes: 25 additions & 0 deletions
25
...ain/java/org/openmainframeproject/cobolcheck/features/interpreter/SectionOrParagraph.java
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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(); | ||
} | ||
} |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -165,4 +165,5 @@ private String getArgumentText(){ | |
} | ||
return combinedArgs.substring(0, combinedArgs.length() - 2); | ||
} | ||
|
||
} |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
65 changes: 65 additions & 0 deletions
65
src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/WhenOther.java
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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; | ||
|
||
} | ||
|
||
} |
37 changes: 37 additions & 0 deletions
37
...java/org/openmainframeproject/cobolcheck/features/testSuiteParser/WhenOtherGenerator.java
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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); | ||
} | ||
|
||
|
||
} |
Oops, something went wrong.