Skip to content

Commit fcdc76e

Browse files
authored
Merge pull request #383 from thomasNellemann-BD/add-replace-to-unit-test-source
Add replace to unit test source and COBOL program
2 parents 4e73165 + fbb3ada commit fcdc76e

File tree

14 files changed

+347
-65
lines changed

14 files changed

+347
-65
lines changed

src/main/cobol/GREETING.CBL

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@
1616
01 WS-FRIEND PIC X(10) VALUE SPACES.
1717
01 WS-GREETING.
1818
10 FILLER PIC X(07) VALUE 'Hello, '.
19-
10 WS-USER-NAME PIC X(06) VALUE SPACES.
19+
10 WS-USER-NAME PIC X(05) VALUE SPACES.
2020
10 FILLER PIC X VALUE '!'.
2121
01 WS-FAREWELL.
2222
10 FILLER PIC X(15) VALUE 'See you later, '.

src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/TestSuiteConcatenator.java

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -106,9 +106,12 @@ Reader concatenateTestSuites(String programTestSuiteSubdirectory) {
106106
for (String matchingFile : matchingFiles) {
107107
BufferedReader testFileReader = new BufferedReader(EncodingIO.getReaderWithCorrectEncoding(matchingFile));
108108
String line = Constants.EMPTY_STRING;
109+
// Line number is set to zero, to be used in Replace.replace() method
110+
// So that replace is performed regardless of line number
111+
int lineNumber = 0;
109112
concatenatedTestSuitesWriter.write(StringHelper.commentOutLine("From file: " + matchingFile) + Constants.NEWLINE);
110113
while((line = testFileReader.readLine()) != null) {
111-
concatenatedTestSuitesWriter.write(Replace.replace(line) + Constants.NEWLINE);
114+
concatenatedTestSuitesWriter.write(Replace.replace(line, lineNumber) + Constants.NEWLINE);
112115
}
113116
testFileReader.close();
114117
}

src/main/java/org/openmainframeproject/cobolcheck/features/testSuiteParser/TestSuiteParser.java

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -882,7 +882,6 @@ private void handleEndOfMockStatement(BufferedReader testSuiteReader, String tes
882882
*
883883
* @param parsedTestSuiteLines The parsed lines, that the generated lines are
884884
* appended to
885-
* @return - the next token from the testSuiteReader.
886885
* @throws VerifyReferencesNonexistentMockException if referenced mock, does not
887886
* exist
888887
*/

src/main/java/org/openmainframeproject/cobolcheck/services/StringHelper.java

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -90,7 +90,7 @@ public static String changeFileExtension(String path, String extension){
9090

9191
/**
9292
* Trims only the end of the string.
93-
* Ex.: " Hey \n" => " Hey"
93+
* Ex.: " Hey \n" ~ " Hey"
9494
*
9595
* @param line - original string
9696
* @return - string trimmed at the end.
@@ -123,7 +123,7 @@ public static boolean occursFirst (String text, char expectedFirst, char expecte
123123

124124
/**
125125
* Swaps two characters in a given string.
126-
* Example: swapChars("1.000.000,00", '.', ',') => "1,000,000.00"
126+
* Example: swapChars("1.000.000,00", '.', ',') ~ "1,000,000.00"
127127
* @param c1 - One of the chars to swap
128128
* @param c2 - One of the chars to swap
129129
* @return - The given string with the given char values swapped

src/main/java/org/openmainframeproject/cobolcheck/services/cobolLogic/replace/Replace.java

Lines changed: 37 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,6 @@
44
import org.openmainframeproject.cobolcheck.services.log.LogLevel;
55

66
import java.io.*;
7-
import java.util.HashMap;
8-
import java.util.Iterator;
97
import java.util.LinkedList;
108
import java.util.regex.Matcher;
119
import java.util.regex.Pattern;
@@ -60,9 +58,10 @@ public class Replace {
6058
* Looks in the source line for the replace-key and replaces is with the replace-to-value.
6159
*
6260
* @param source a line of cobol-check unit test code
61+
* @param lineNumber the line number of the source line
6362
* @return the source line there the appropriate replacement has been made
6463
*/
65-
public static String replace(String source) {
64+
public static String replace(String source, int lineNumber) {
6665
if (!inspect_performed) {
6766
if (!inspect_performed_warned) {
6867
inspect_performed_warned = true;
@@ -86,14 +85,18 @@ public static String replace(String source) {
8685

8786
for (ReplaceSet replaceSet : replaceMap) {
8887
Log.trace("Replace.replace(): Key: <" + replaceSet.getFrom() + ">, Value: <" + replaceSet.getTo() + ">");
89-
replacesString = replaceSet.replaceInline(replacesString);
88+
replacesString = replaceSet.replaceInline(replacesString, lineNumber);
9089
if ((Log.level() == LogLevel.TRACE) && (!replacesString.equals(source))) {
9190
Log.trace("Replace.replace(): Key: <" + replaceSet.getFrom() + ">, result: " + replacesString);
9291
}
9392
}
9493
return replacesString;
9594
}
9695

96+
public static String replace(String source) {
97+
return replace(source, 0);
98+
}
99+
97100

98101
public static void inspectProgram(File cobolProgram) {
99102
Log.trace("Replace.inspectProgram(): Inspecting the COBOL program file: " + cobolProgram);
@@ -152,4 +155,34 @@ private static void reset() {
152155
inspect_performed = false;
153156
inspect_performed_warned = false;
154157
}
158+
159+
public static String replaceInProgram(File program) {
160+
// write the replaced program back to disk
161+
162+
String newFileName = program+"_MOD";
163+
Log.warn("Replace.replaceInProgram(): Writing the COBOL program file: " + newFileName);
164+
try {
165+
BufferedWriter writer = new BufferedWriter(new FileWriter(newFileName));
166+
// read the program one line at the time
167+
BufferedReader reader = new BufferedReader(new FileReader(program));
168+
//for every line in the program, replace and write to output file
169+
String line;
170+
int lineCount = 0;
171+
while ((line = reader.readLine()) != null) {
172+
writer.write(Replace.replace(line, lineCount++));
173+
writer.newLine();
174+
}
175+
writer.close();
176+
reader.close();
177+
} catch (IOException e) {
178+
Log.error("Replace.replaceInProgram(): Error writing the COBOL program file: " + program);
179+
}
180+
return newFileName;
181+
}
182+
183+
public static void showReplaceSets() {
184+
for (ReplaceSet replaceSet : replaceMap) {
185+
Log.info("Replace.showReplaceSets():" + replaceSet.toString());
186+
}
187+
}
155188
}

src/main/java/org/openmainframeproject/cobolcheck/services/cobolLogic/replace/ReplaceSet.java

Lines changed: 52 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,13 +4,21 @@
44
import java.util.regex.Matcher;
55
import java.util.regex.Pattern;
66

7+
/**
8+
* Class to handle the COBOL REPLACE statement keys on the test suite/test case source code.
9+
* <p>
10+
* When fromSourceLine and untilSourceLine are set, the replace is only performed on the lines between these two lines.
11+
* When the values are zero, the replace key set is applied to all lines.
12+
*/
713
public class ReplaceSet {
814
private String from;
915
private String to;
1016
private boolean trailing;
1117
private boolean leading;
18+
private int fromSourceLine;
19+
private int untilSourceLine;
1220

13-
public ReplaceSet(String from, String to, boolean trailing, boolean leading) {
21+
public ReplaceSet(String from, String to, boolean trailing, boolean leading,int fromSourceLine, int untilSourceLine) {
1422
if (trailing && leading) {
1523
throw new IllegalArgumentException("Cannot have both trailing and leading set to true");
1624
}
@@ -19,17 +27,21 @@ public ReplaceSet(String from, String to, boolean trailing, boolean leading) {
1927
this.to = to;
2028
this.trailing = trailing;
2129
this.leading = leading;
30+
this.fromSourceLine = fromSourceLine;
31+
this.untilSourceLine = untilSourceLine;
2232
}
2333

2434
public ReplaceSet() {
2535
this.from = "";
2636
this.to = "";
2737
this.trailing = false;
2838
this.leading = false;
39+
this.fromSourceLine = 0;
40+
this.untilSourceLine = 0;
2941
}
3042

3143
/**
32-
* Perform 'Replace' in the string (line param). Correponding to the 'REPLACE' statement in COBOL program
44+
* Perform 'Replace' in the string (line param). Corresponding to the 'REPLACE' statement in COBOL program
3345
* And the values parsed from the statements are used to replace the values in the line.
3446
*
3547
* @param line The line to replace in
@@ -60,6 +72,28 @@ public String replaceInline(String line) {
6072
}
6173
}
6274

75+
/**
76+
* Perform 'Replace' in the string (line param). Corresponding to the 'REPLACE' statement in COBOL program
77+
* And the values parsed from the statements are used to replace the values in the line.
78+
* @param line
79+
* @param sourceLine
80+
* @return
81+
*/
82+
public String replaceInline(String line, int sourceLine) {
83+
// if the line is zero, the replace key set is applied
84+
if (sourceLine == 0) return replaceInline(line);
85+
86+
// when fromSourceLine and untilSourceLine are zero, the replace key set is applied to all lines.
87+
if (fromSourceLine == 0 && untilSourceLine == 0) return replaceInline(line);
88+
89+
// when the line number is between fromSourceLine and untilSourceLine, the replace is performed
90+
if ((sourceLine >= fromSourceLine && sourceLine <= untilSourceLine) ||
91+
((sourceLine >= fromSourceLine && untilSourceLine == 0))) return replaceInline(line);
92+
93+
// Otherwise, return the line as is
94+
return line;
95+
}
96+
6397
public void setTrailing(boolean trailing) {
6498
if (trailing && this.leading) {
6599
throw new IllegalArgumentException("Cannot have both trailing and leading set to true");
@@ -97,4 +131,20 @@ public boolean isTrailing() {
97131
public boolean isLeading() {
98132
return leading;
99133
}
134+
135+
public void setFromSourceLine(int sourceLineNumber) {
136+
this.fromSourceLine = sourceLineNumber;
137+
}
138+
public void setUntilSourceLine(int sourceLineNumber) {
139+
this.untilSourceLine = sourceLineNumber;
140+
}
141+
public int getFromSourceLine() {
142+
return fromSourceLine;
143+
}
144+
public int getUntilSourceLine() {
145+
return untilSourceLine;
146+
}
147+
public String toString() {
148+
return "From: " + from + ", To: " + to + ", Trailing: " + trailing + ", Leading: " + leading + ", FromSourceLine: " + fromSourceLine + ", UntilSourceLine: " + untilSourceLine;
149+
}
100150
}

src/main/java/org/openmainframeproject/cobolcheck/services/cobolLogic/replace/ReplaceStatementLocator.java

Lines changed: 33 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
package org.openmainframeproject.cobolcheck.services.cobolLogic.replace;
22

3+
import org.jetbrains.annotations.NotNull;
34
import org.openmainframeproject.cobolcheck.services.log.Log;
45

56
import java.io.*;
@@ -16,9 +17,11 @@ public class ReplaceStatementLocator {
1617
// because it can be split over multiple lines
1718
private final ReplaceTokenizer tokenizer = new ReplaceTokenizer();
1819
protected StringBuilder currentStatement;
20+
protected int statementLineNumber = 0;
1921
protected boolean we_are_parsing_a_replace_statement = false;
2022
protected int sourceLinesProcessed = 0;
2123
protected int commentLinesFound = 0;
24+
private int currentSourcecodeLine = -1;
2225

2326
public ReplaceStatementLocator() {
2427
Log.trace("ReplaceStatementLocator(): No file provided, only for testing purposes");
@@ -29,8 +32,9 @@ public ReplaceStatementLocator(File cobolFile) {
2932
//Iterate over the file and inspect each line
3033
try (BufferedReader reader = new BufferedReader(new FileReader(cobolFile))) {
3134
String line;
35+
int lineCounter = 0;
3236
while ((line = reader.readLine()) != null) {
33-
accumulateStatement(line);
37+
accumulateStatement(line,++lineCounter);
3438
}
3539
} catch (FileNotFoundException e) {
3640
Log.error("ReplaceStatementLocator(): File not found: " + e.getMessage());
@@ -45,7 +49,7 @@ public LinkedList<ReplaceSet> getReplaceSets() {
4549
return replaceSets;
4650
}
4751

48-
protected void accumulateStatement(String line) {
52+
protected void accumulateStatement(String line, int sourceLineNumber) {
4953
// tokenize the line
5054
tokenizer.tokenize(line);
5155

@@ -66,25 +70,40 @@ protected void accumulateStatement(String line) {
6670
if (t.getType() == ReplaceTokenType.REPLACE) {
6771
// if we have a REPLACE token, start accumulating the statement
6872
currentStatement = new StringBuilder().append(t.getValue());
73+
this.statementLineNumber = sourceLineNumber;
6974
we_are_parsing_a_replace_statement = true;
7075
} else if (t.getType() == ReplaceTokenType.TERMINATOR && we_are_parsing_a_replace_statement) {
7176
// if we have a terminator token, process the statement
72-
createStatements(currentStatement.toString());
77+
createStatements(currentStatement.toString(),this.statementLineNumber);
7378
we_are_parsing_a_replace_statement = false;
7479
}
7580
}
7681
}
7782

83+
/**
84+
* Update the untilSourceLine in all ReplaceSet objects where the from is equal to the given value
85+
* @param untilSourceLine the new value for untilSourceLine
86+
*/
87+
protected void updateUntilInReplaceSets(int fromSourceLine, int untilSourceLine) {
88+
for (ReplaceSet replaceSet : replaceSets) {
89+
if (replaceSet.getFromSourceLine() == fromSourceLine) replaceSet.setUntilSourceLine(untilSourceLine);
90+
}
91+
}
92+
7893

7994
/**
8095
* process a complete <i>REPLACE</i> statement and create the ReplaceSet objects
8196
* @param statement string of tokens from replace to terminator (.)
8297
*/
83-
protected void createStatements(String statement) {
98+
protected void createStatements(String statement, int sourceLineNumber) {
8499
ReplaceTokenizer statementTokenizer = new ReplaceTokenizer();
85100
statementTokenizer.tokenize(statement);
86101

87-
ReplaceSet replaceSet = new ReplaceSet();
102+
ReplaceSet replaceSet = getNewReplaceSet(sourceLineNumber);
103+
// update the ReplaceSets that may have been created from the 'currentSourcecodeLine' location
104+
// from and to values are corrected to avoid replacing the REPLACE statement itself
105+
this.updateUntilInReplaceSets(this.currentSourcecodeLine + 1,sourceLineNumber - 1);
106+
this.currentSourcecodeLine = sourceLineNumber;
88107

89108
ReplaceToken t;
90109
boolean nextTokenIsTo = false;
@@ -111,12 +130,20 @@ protected void createStatements(String statement) {
111130
replaceSet.setTo(t.getValue().replace("==", ""));
112131
nextTokenIsTo = false;
113132
replaceSets.add(replaceSet);
114-
replaceSet = new ReplaceSet();
133+
replaceSet = getNewReplaceSet(sourceLineNumber);
115134
} else {
116135
replaceSet.setFrom(t.getValue().replace("==", ""));
117136
}
118137
break;
119138
}
120139
}
121140
}
141+
142+
private static @NotNull ReplaceSet getNewReplaceSet(int sourceLineNumber) {
143+
ReplaceSet replaceSet = new ReplaceSet();
144+
// one is added to the sourceLineNumber because the REPLACE statement is on current line and the replace is done from the next line
145+
// This way we won´t replace the REPLACE statement itself
146+
replaceSet.setFromSourceLine(sourceLineNumber + 1);
147+
return replaceSet;
148+
}
122149
}

src/main/java/org/openmainframeproject/cobolcheck/workers/Generator.java

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -68,9 +68,12 @@ public Generator(InterpreterController interpreter, WriterController writerContr
6868
public void prepareAndRunMerge(String programName, String testFileNames) {
6969
RunInfo.setCurrentProgramName(new File(programName).getName());
7070
RunInfo.setCurrentProgramPath(new File(programName).getAbsolutePath());
71-
Replace.inspectProgram(new File(PathHelper.appendMatchingFileSuffix(programName, Config.getApplicationFilenameSuffixes())));
71+
File originalSource = new File(PathHelper.appendMatchingFileSuffix(programName, Config.getApplicationFilenameSuffixes()));
72+
Replace.inspectProgram(originalSource);
7273

7374
matchingTestDirectories = PrepareMergeController.getMatchingTestDirectoriesForProgram(programName);
75+
//replace in the program, return the program name with the corrected source code.
76+
programName = Replace.replaceInProgram(originalSource);
7477
for (String matchingDirectory : matchingTestDirectories) {
7578

7679
Reader sourceReader = PrepareMergeController.getSourceReader(programName);

src/test/cobol/GREETING/GreetingByName.cut

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,11 +7,11 @@
77
PERFORM 2000-SPEAK
88
EXPECT WS-GREETING TO BE "Hello, James!"
99

10-
TESTCASE "When message type is farewell it returns Goodbye, James!"
10+
TESTCASE "When message type is farewell it returns Goodbye, James !"
1111
SET MESSAGE-IS-FAREWELL TO TRUE
1212
MOVE "James" TO WS-FRIEND
1313
PERFORM 2000-SPEAK
14-
EXPECT WS-FAREWELL TO BE "Goodbye, James!"
14+
EXPECT WS-FAREWELL TO BE "See you later, James !"
1515

1616
TESTCASE "User name for greeting and farewell are consistent"
1717
SET MESSAGE-IS-GREETING TO TRUE

src/test/cobol/GREETING/GreetingByType.cut

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
"Greeting returns the appropriate message based on message type"
33

44
TestCase "When message type is greeting it returns 'Hello, World!'"
5+
move space to WS-FRIEND
56
SET MESSAGE-IS-GREETING TO TRUE
67
PERFORM 2000-SPEAK
78
EXPECT WS-GREETING TO BE "Hello, World!"
@@ -11,6 +12,7 @@
1112
EXPECT WS-COUNT TO BE 1
1213

1314
TESTCASE "try 88 level compare"
15+
set message-is-farewell to true
1416
EXPECT MESSAGE-IS-GREETING TO BE FALSE
1517

1618
TESTCASE "When message type is farewell it returns See you later, alligator!"
@@ -19,6 +21,6 @@
1921
Expect WS-FAREWELL To Be "See you later, alligator!"
2022

2123
TESTCASE "Message type greeting is not true"
22-
SET MESSAGE-IS-GREETING TO TRUE
24+
SET MESSAGE-IS-FAREWELL TO TRUE
2325
Expect MESSAGE-IS-GREETING NOT TO BE TRUE
2426

0 commit comments

Comments
 (0)