Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion src/main/cobol/GREETING.CBL
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@
01 WS-FRIEND PIC X(10) VALUE SPACES.
01 WS-GREETING.
10 FILLER PIC X(07) VALUE 'Hello, '.
10 WS-USER-NAME PIC X(06) VALUE SPACES.
10 WS-USER-NAME PIC X(05) VALUE SPACES.
10 FILLER PIC X VALUE '!'.
01 WS-FAREWELL.
10 FILLER PIC X(15) VALUE 'See you later, '.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -106,9 +106,12 @@ Reader concatenateTestSuites(String programTestSuiteSubdirectory) {
for (String matchingFile : matchingFiles) {
BufferedReader testFileReader = new BufferedReader(EncodingIO.getReaderWithCorrectEncoding(matchingFile));
String line = Constants.EMPTY_STRING;
// Line number is set to zero, to be used in Replace.replace() method
// So that replace is performed regardless of line number
int lineNumber = 0;
concatenatedTestSuitesWriter.write(StringHelper.commentOutLine("From file: " + matchingFile) + Constants.NEWLINE);
while((line = testFileReader.readLine()) != null) {
concatenatedTestSuitesWriter.write(Replace.replace(line) + Constants.NEWLINE);
concatenatedTestSuitesWriter.write(Replace.replace(line, lineNumber) + Constants.NEWLINE);
}
testFileReader.close();
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -882,7 +882,6 @@ private void handleEndOfMockStatement(BufferedReader testSuiteReader, String tes
*
* @param parsedTestSuiteLines The parsed lines, that the generated lines are
* appended to
* @return - the next token from the testSuiteReader.
* @throws VerifyReferencesNonexistentMockException if referenced mock, does not
* exist
*/
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -90,7 +90,7 @@ public static String changeFileExtension(String path, String extension){

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

/**
* Swaps two characters in a given string.
* Example: swapChars("1.000.000,00", '.', ',') => "1,000,000.00"
* Example: swapChars("1.000.000,00", '.', ',') ~ "1,000,000.00"
* @param c1 - One of the chars to swap
* @param c2 - One of the chars to swap
* @return - The given string with the given char values swapped
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,6 @@
import org.openmainframeproject.cobolcheck.services.log.LogLevel;

import java.io.*;
import java.util.HashMap;
import java.util.Iterator;
import java.util.LinkedList;
import java.util.regex.Matcher;
import java.util.regex.Pattern;
Expand Down Expand Up @@ -60,9 +58,10 @@ public class Replace {
* Looks in the source line for the replace-key and replaces is with the replace-to-value.
*
* @param source a line of cobol-check unit test code
* @param lineNumber the line number of the source line
* @return the source line there the appropriate replacement has been made
*/
public static String replace(String source) {
public static String replace(String source, int lineNumber) {
if (!inspect_performed) {
if (!inspect_performed_warned) {
inspect_performed_warned = true;
Expand All @@ -86,14 +85,18 @@ public static String replace(String source) {

for (ReplaceSet replaceSet : replaceMap) {
Log.trace("Replace.replace(): Key: <" + replaceSet.getFrom() + ">, Value: <" + replaceSet.getTo() + ">");
replacesString = replaceSet.replaceInline(replacesString);
replacesString = replaceSet.replaceInline(replacesString, lineNumber);
if ((Log.level() == LogLevel.TRACE) && (!replacesString.equals(source))) {
Log.trace("Replace.replace(): Key: <" + replaceSet.getFrom() + ">, result: " + replacesString);
}
}
return replacesString;
}

public static String replace(String source) {
return replace(source, 0);
}


public static void inspectProgram(File cobolProgram) {
Log.trace("Replace.inspectProgram(): Inspecting the COBOL program file: " + cobolProgram);
Expand Down Expand Up @@ -152,4 +155,34 @@ private static void reset() {
inspect_performed = false;
inspect_performed_warned = false;
}

public static String replaceInProgram(File program) {
// write the replaced program back to disk

String newFileName = program+"_MOD";
Log.warn("Replace.replaceInProgram(): Writing the COBOL program file: " + newFileName);
try {
BufferedWriter writer = new BufferedWriter(new FileWriter(newFileName));
// read the program one line at the time
BufferedReader reader = new BufferedReader(new FileReader(program));
//for every line in the program, replace and write to output file
String line;
int lineCount = 0;
while ((line = reader.readLine()) != null) {
writer.write(Replace.replace(line, lineCount++));
writer.newLine();
}
writer.close();
reader.close();
} catch (IOException e) {
Log.error("Replace.replaceInProgram(): Error writing the COBOL program file: " + program);
}
return newFileName;
}

public static void showReplaceSets() {
for (ReplaceSet replaceSet : replaceMap) {
Log.info("Replace.showReplaceSets():" + replaceSet.toString());
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -4,13 +4,21 @@
import java.util.regex.Matcher;
import java.util.regex.Pattern;

/**
* Class to handle the COBOL REPLACE statement keys on the test suite/test case source code.
* <p>
* When fromSourceLine and untilSourceLine are set, the replace is only performed on the lines between these two lines.
* When the values are zero, the replace key set is applied to all lines.
*/
public class ReplaceSet {
private String from;
private String to;
private boolean trailing;
private boolean leading;
private int fromSourceLine;
private int untilSourceLine;

public ReplaceSet(String from, String to, boolean trailing, boolean leading) {
public ReplaceSet(String from, String to, boolean trailing, boolean leading,int fromSourceLine, int untilSourceLine) {
if (trailing && leading) {
throw new IllegalArgumentException("Cannot have both trailing and leading set to true");
}
Expand All @@ -19,17 +27,21 @@ public ReplaceSet(String from, String to, boolean trailing, boolean leading) {
this.to = to;
this.trailing = trailing;
this.leading = leading;
this.fromSourceLine = fromSourceLine;
this.untilSourceLine = untilSourceLine;
}

public ReplaceSet() {
this.from = "";
this.to = "";
this.trailing = false;
this.leading = false;
this.fromSourceLine = 0;
this.untilSourceLine = 0;
}

/**
* Perform 'Replace' in the string (line param). Correponding to the 'REPLACE' statement in COBOL program
* Perform 'Replace' in the string (line param). Corresponding to the 'REPLACE' statement in COBOL program
* And the values parsed from the statements are used to replace the values in the line.
*
* @param line The line to replace in
Expand Down Expand Up @@ -60,6 +72,28 @@ public String replaceInline(String line) {
}
}

/**
* Perform 'Replace' in the string (line param). Corresponding to the 'REPLACE' statement in COBOL program
* And the values parsed from the statements are used to replace the values in the line.
* @param line
* @param sourceLine
* @return
*/
public String replaceInline(String line, int sourceLine) {
// if the line is zero, the replace key set is applied
if (sourceLine == 0) return replaceInline(line);

// when fromSourceLine and untilSourceLine are zero, the replace key set is applied to all lines.
if (fromSourceLine == 0 && untilSourceLine == 0) return replaceInline(line);

// when the line number is between fromSourceLine and untilSourceLine, the replace is performed
if ((sourceLine >= fromSourceLine && sourceLine <= untilSourceLine) ||
((sourceLine >= fromSourceLine && untilSourceLine == 0))) return replaceInline(line);

// Otherwise, return the line as is
return line;
}

public void setTrailing(boolean trailing) {
if (trailing && this.leading) {
throw new IllegalArgumentException("Cannot have both trailing and leading set to true");
Expand Down Expand Up @@ -97,4 +131,20 @@ public boolean isTrailing() {
public boolean isLeading() {
return leading;
}

public void setFromSourceLine(int sourceLineNumber) {
this.fromSourceLine = sourceLineNumber;
}
public void setUntilSourceLine(int sourceLineNumber) {
this.untilSourceLine = sourceLineNumber;
}
public int getFromSourceLine() {
return fromSourceLine;
}
public int getUntilSourceLine() {
return untilSourceLine;
}
public String toString() {
return "From: " + from + ", To: " + to + ", Trailing: " + trailing + ", Leading: " + leading + ", FromSourceLine: " + fromSourceLine + ", UntilSourceLine: " + untilSourceLine;
}
}
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
package org.openmainframeproject.cobolcheck.services.cobolLogic.replace;

import org.jetbrains.annotations.NotNull;
import org.openmainframeproject.cobolcheck.services.log.Log;

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

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

protected void accumulateStatement(String line) {
protected void accumulateStatement(String line, int sourceLineNumber) {
// tokenize the line
tokenizer.tokenize(line);

Expand All @@ -66,25 +70,40 @@ protected void accumulateStatement(String line) {
if (t.getType() == ReplaceTokenType.REPLACE) {
// if we have a REPLACE token, start accumulating the statement
currentStatement = new StringBuilder().append(t.getValue());
this.statementLineNumber = sourceLineNumber;
we_are_parsing_a_replace_statement = true;
} else if (t.getType() == ReplaceTokenType.TERMINATOR && we_are_parsing_a_replace_statement) {
// if we have a terminator token, process the statement
createStatements(currentStatement.toString());
createStatements(currentStatement.toString(),this.statementLineNumber);
we_are_parsing_a_replace_statement = false;
}
}
}

/**
* Update the untilSourceLine in all ReplaceSet objects where the from is equal to the given value
* @param untilSourceLine the new value for untilSourceLine
*/
protected void updateUntilInReplaceSets(int fromSourceLine, int untilSourceLine) {
for (ReplaceSet replaceSet : replaceSets) {
if (replaceSet.getFromSourceLine() == fromSourceLine) replaceSet.setUntilSourceLine(untilSourceLine);
}
}


/**
* process a complete <i>REPLACE</i> statement and create the ReplaceSet objects
* @param statement string of tokens from replace to terminator (.)
*/
protected void createStatements(String statement) {
protected void createStatements(String statement, int sourceLineNumber) {
ReplaceTokenizer statementTokenizer = new ReplaceTokenizer();
statementTokenizer.tokenize(statement);

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

ReplaceToken t;
boolean nextTokenIsTo = false;
Expand All @@ -111,12 +130,20 @@ protected void createStatements(String statement) {
replaceSet.setTo(t.getValue().replace("==", ""));
nextTokenIsTo = false;
replaceSets.add(replaceSet);
replaceSet = new ReplaceSet();
replaceSet = getNewReplaceSet(sourceLineNumber);
} else {
replaceSet.setFrom(t.getValue().replace("==", ""));
}
break;
}
}
}

private static @NotNull ReplaceSet getNewReplaceSet(int sourceLineNumber) {
ReplaceSet replaceSet = new ReplaceSet();
// one is added to the sourceLineNumber because the REPLACE statement is on current line and the replace is done from the next line
// This way we won´t replace the REPLACE statement itself
replaceSet.setFromSourceLine(sourceLineNumber + 1);
return replaceSet;
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -68,9 +68,12 @@ public Generator(InterpreterController interpreter, WriterController writerContr
public void prepareAndRunMerge(String programName, String testFileNames) {
RunInfo.setCurrentProgramName(new File(programName).getName());
RunInfo.setCurrentProgramPath(new File(programName).getAbsolutePath());
Replace.inspectProgram(new File(PathHelper.appendMatchingFileSuffix(programName, Config.getApplicationFilenameSuffixes())));
File originalSource = new File(PathHelper.appendMatchingFileSuffix(programName, Config.getApplicationFilenameSuffixes()));
Replace.inspectProgram(originalSource);

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

Reader sourceReader = PrepareMergeController.getSourceReader(programName);
Expand Down
4 changes: 2 additions & 2 deletions src/test/cobol/GREETING/GreetingByName.cut
Original file line number Diff line number Diff line change
Expand Up @@ -7,11 +7,11 @@
PERFORM 2000-SPEAK
EXPECT WS-GREETING TO BE "Hello, James!"

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

TESTCASE "User name for greeting and farewell are consistent"
SET MESSAGE-IS-GREETING TO TRUE
Expand Down
4 changes: 3 additions & 1 deletion src/test/cobol/GREETING/GreetingByType.cut
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
"Greeting returns the appropriate message based on message type"

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

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

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

TESTCASE "Message type greeting is not true"
SET MESSAGE-IS-GREETING TO TRUE
SET MESSAGE-IS-FAREWELL TO TRUE
Expect MESSAGE-IS-GREETING NOT TO BE TRUE

Loading
Loading