Skip to content

Commit

Permalink
item #10 started to implement keyword parsing support for test suites
Browse files Browse the repository at this point in the history
  • Loading branch information
davenicolette committed Dec 29, 2020
1 parent 74a8f80 commit bc04310
Show file tree
Hide file tree
Showing 34 changed files with 2,195 additions and 21 deletions.
5 changes: 4 additions & 1 deletion pad
Original file line number Diff line number Diff line change
@@ -1,2 +1,5 @@
# Pad all lines of a text file to 80 characters plus newline
awk -F, '{printf("%80-s\n", $1)}' "$1" > "$2"
paddir="$1"
padsource="$2"
padtarget="$3"
awk -F, '{printf("%80-s\n", $1)}' "$paddir/$padsource" > "$paddir/$padtarget"
8 changes: 8 additions & 0 deletions src/main/java/com/neopragma/cobolcheck/Constants.java
Original file line number Diff line number Diff line change
Expand Up @@ -28,4 +28,12 @@ public interface Constants {
String COMMA = ",";
String PSEUDO_TEXT_DELIMITER_EQUALS = "==";
String PSEUDO_TEXT_DELIMITER_COLON = "::";
String TRUE = "TRUE";
String FALSE = "FALSE";
String EXPECT_KEYWORD = "EXPECT";
String FIELDNAME_KEYWORD = "fieldname";
String TO_BE_KEYWORD = "TO BE";
String NOT_KEYWORD = "NOT";
String ALPHANUMERIC_LITERAL_KEYWORD = "alphanumeric-literal";
String NUMERIC_LITERAL_KEYWORD = "numeric-literal";
}
4 changes: 3 additions & 1 deletion src/main/java/com/neopragma/cobolcheck/Generator.java
Original file line number Diff line number Diff line change
Expand Up @@ -53,6 +53,8 @@ public class Generator implements Constants, StringHelper {
private final String workingStorageHeader = fixedLength(" WORKING-STORAGE SECTION.");
private static String copybookDirectoryName = EMPTY_STRING;

private static final String performUTInitialize = " PERFORM UT-INITIALIZE";

private Reader secondarySourceReader;

public Generator(
Expand Down Expand Up @@ -153,9 +155,9 @@ private void insertWorkingStorageTestCode(Writer testSourceOut) throws IOExcepti
}

private void insertProcedureDivisionTestCode(Writer testSourceOut) throws IOException {
testSourceOut.write(fixedLength(performUTInitialize));
secondarySourceReader = new FileReader(copybookFile(procedureDivisionCopybookFilename));
insertSecondarySourceIntoTestSource(testSourceOut);
workingStorageTestCodeHasBeenInserted = true;
}

private void insertSecondarySourceIntoTestSource(Writer testSourceOut) throws IOException {
Expand Down
33 changes: 33 additions & 0 deletions src/main/java/com/neopragma/cobolcheck/Keyword.java
Original file line number Diff line number Diff line change
@@ -0,0 +1,33 @@
/*
Copyright 2020 David Nicolette
Licensed under the Apache License, Version 2.0 (the "License");
you may not use this file except in compliance with the License.
You may obtain a copy of the License at
http://www.apache.org/licenses/LICENSE-2.0
Unless required by applicable law or agreed to in writing, software
distributed under the License is distributed on an "AS IS" BASIS,
WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
See the License for the specific language governing permissions and
limitations under the License.
*/
package com.neopragma.cobolcheck;

import java.util.List;

/**
* This record encapsulates information about a cobol-check keyword.
*
* value = the value of the keyword as a string (note that some keywords have embedded spaces, like "TO BE")
* validNextKey = list of keys in Keywords for tokens that may follow the current keyword in the test suite.
* keywordAction = special handling for this keyword, if any.
*
* @author Dave Nicolette (neopragma)
* @since 14
*/
public record Keyword(
String value,
List<String> validNextKey,
KeywordAction keywordAction) { }
39 changes: 39 additions & 0 deletions src/main/java/com/neopragma/cobolcheck/KeywordAction.java
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
/*
Copyright 2020 David Nicolette
Licensed under the Apache License, Version 2.0 (the "License");
you may not use this file except in compliance with the License.
You may obtain a copy of the License at
http://www.apache.org/licenses/LICENSE-2.0
Unless required by applicable law or agreed to in writing, software
distributed under the License is distributed on an "AS IS" BASIS,
WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
See the License for the specific language governing permissions and
limitations under the License.
*/
package com.neopragma.cobolcheck;

/**
* Special handling pertaining to a cobol-check keyword. Used when parsing a testsuite and inserting the
* corresponding Cobol code into the program under test. KeywordAction is a member of record type Keyword.
*
* NONE - no special action is associated with this keyword
* ACTUAL_FIELDNAME - the next token will be the fieldname of the actual (result) value for an EXPECT
* EXPECTED_VALUE - the next token will be the expected value for an EXPECT
* REVERSE_LOGIC - the comparison logic for this EXPECT is to be reversed (NOT logic)
* IGNORE - the next token will be TESTCASE - bypass that test case
* FIELDNAME - this token is the name of a field in the Data Division of the program under test
*
* @author Dave Nicolette (neopragma)
* @since 14
*/
public enum KeywordAction {
NONE,
ACTUAL_FIELDNAME,
EXPECTED_VALUE,
REVERSE_LOGIC,
IGNORE,
FIELDNAME
}
72 changes: 72 additions & 0 deletions src/main/java/com/neopragma/cobolcheck/Keywords.java
Original file line number Diff line number Diff line change
@@ -0,0 +1,72 @@
/*
Copyright 2020 David Nicolette
Licensed under the Apache License, Version 2.0 (the "License");
you may not use this file except in compliance with the License.
You may obtain a copy of the License at
http://www.apache.org/licenses/LICENSE-2.0
Unless required by applicable law or agreed to in writing, software
distributed under the License is distributed on an "AS IS" BASIS,
WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
See the License for the specific language governing permissions and
limitations under the License.
*/
package com.neopragma.cobolcheck;

import com.neopragma.cobolcheck.exceptions.UndefinedKeywordException;

import java.util.HashMap;
import java.util.List;
import java.util.Map;

/**
* This is a container for Keyword records. It is used when parsing test suites to identify cobol-check
* keywords and handle them appropriately.
*
* @author Dave Nicolette (neopragma)
* @since 14
*/
public class Keywords implements Constants {
private static final Messages messages = new Messages();
private static final Map<String, Keyword> keywordInfo;

static {
keywordInfo = new HashMap<>();
keywordInfo.put(EXPECT_KEYWORD,
new Keyword(EXPECT_KEYWORD, List.of(FIELDNAME_KEYWORD),
KeywordAction.ACTUAL_FIELDNAME));
keywordInfo.put(FIELDNAME_KEYWORD,
new Keyword(EMPTY_STRING, List.of(TO_BE_KEYWORD, NOT_KEYWORD),
KeywordAction.FIELDNAME));
keywordInfo.put(NOT_KEYWORD,
new Keyword(NOT_KEYWORD, List.of(TO_BE_KEYWORD),
KeywordAction.REVERSE_LOGIC));
keywordInfo.put(TO_BE_KEYWORD,
new Keyword(TO_BE_KEYWORD,
List.of(FIELDNAME_KEYWORD,
"alphanumeric-literal",
"numeric-literal",
TRUE,
FALSE),
KeywordAction.EXPECTED_VALUE));
keywordInfo.put("alphanumeric-literal",
new Keyword(EMPTY_STRING, List.of(),
KeywordAction.FIELDNAME));
keywordInfo.put("numeric-literal",
new Keyword(EMPTY_STRING, List.of(),
KeywordAction.FIELDNAME));
}

public static Keyword getKeywordFor(String key) {
Keyword result = keywordInfo.get(key);
if (result == null) {
throw new UndefinedKeywordException(
messages.get("ERR009",
key)
);
}
return result;
}
}
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
/*
Copyright 2020 David Nicolette
Licensed under the Apache License, Version 2.0 (the "License");
you may not use this file except in compliance with the License.
You may obtain a copy of the License at
http://www.apache.org/licenses/LICENSE-2.0
Unless required by applicable law or agreed to in writing, software
distributed under the License is distributed on an "AS IS" BASIS,
WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
See the License for the specific language governing permissions and
limitations under the License.
*/
package com.neopragma.cobolcheck.exceptions;

public class UndefinedKeywordException extends RuntimeException {
public UndefinedKeywordException(String message) {
super(message);
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -8,5 +8,6 @@ ERR005 = ERR005: Command line option specification string passed to GetOpt was n
ERR006 = ERR006: Expecting a command line option but got <%1$s>.
ERR007 = ERR007: Generator.runSuite() empty input stream (cobolSourceIn).
ERR008 = ERR008: %1$s expected to find a copybook name following COPY verb in <%2$s>.
ERR009 = ERR009: Undefined keyword <%1$s> was encountered while parsing a test suite.
INF001 = INF001: Attempting to load config from %1$s.
INF002 = INF002: Loaded config successfully from %1$s.
Original file line number Diff line number Diff line change
Expand Up @@ -7,5 +7,7 @@ ERR004 = ERR004: Argument für die Befehlszeilenoption <%1$s> erwartet, aber <%
ERR005 = ERR005: Die an GetOpt übergebene Befehlszeilenoptionsspezifikationszeichenfolge war null.
ERR006 = ERR006: Erwartet eine Befehlszeilenoption, hat aber <%1$s>.
ERR007 = ERR007: Generator.runSuite () Leerer Eingabestream (cobolSourceIn).
ERR008 = ERR008: %1$s wird voraussichtlich einen Copybook-Namen nach dem COPY-Verb in <%2$s> finden.
ERR009 = ERR009: Beim Parsen einer Testsuite wurde ein undefiniertes Schlüsselwort <%1$s> gefunden.
INF001 = INF001: Versuch, die Konfiguration von %1$s zu laden.
INF002 = INF002: Die Konfiguration wurde erfolgreich von %1$s geladen.
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@ ERR004 = ERR004: Se esperaba un argumento para la opción de línea de comando <
ERR005 = ERR005: La cadena de especificación de la opción de la línea de comandos pasada a GetOpt era null.
ERR006 = ERR006: Se esperaba una opción de línea de comando, pero obtuvo <%1$s>.
ERR007 = ERR007: Generator.runSuite () inputstream vacío (cobolSourceIn).
ERR008 = ERR008: Se espera que %1$s encuentre un nombre de libro de copias después del verbo COPY en <%2$s>.
ERR009 = ERR009: Se encontró la palabra clave no definida <%1$s> al analizar un conjunto de pruebas.
INF001 = INF001: Intentando cargar la configuración desde %1$s.
INF002 = INF002: Configuración cargada correctamente desde %1$s.
INF003 = INF003: El test suite está vacío en la entrada al método Generator.mergeTestSuite(); nada que hacer aquí.
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@ ERR004 = ERR004: Odotetaan argumenttia komentorivivalinnalle <%1$s>, mutta sai <
ERR005 = ERR005: GetOptille lähetetty komentorivivalinnan määritysmerkkijono oli null.
ERR006 = ERR006: Odotetaan komentorivivaihtoehtoa, mutta sai <%1$s>.
ERR007 = ERR007: Generator.runSuite () tyhjä tulovirta (cobolSourceIn).
ERR008 = ERR008: %1$s odotti löytävän kopiokirjan nimen seuraamalla COPY-verbiä ryhmässä <%2$s>.
ERR009 = ERR009: Määrittelemätön avainsana <%1$s> havaittiin jäsennettäessä testipakettia.
INF001 = INF001: Yritetään ladata määritystä kohteesta %1$s.
INF002 = INF002: Määritys ladattu onnistuneesti kohteesta %1$s.
INF003 = INF003: Test suite on tyhjä tultaessa Generator.mergeTestSuite()-menetelmään; mitään tekemistä täällä.
Original file line number Diff line number Diff line change
Expand Up @@ -7,5 +7,7 @@ ERR004 = ERR004: Attente d'un argument pour l'option de ligne de commande <%1$s>
ERR005 = ERR005: La chaîne de spécification d'option de ligne de commande transmise à GetOpt était null.
ERR006 = ERR006: Attend une option de ligne de commande mais obtient <%1$s>.
ERR007 = ERR007: Generator.runSuite () flux d'entrée vide (cobolSourceIn).
ERR008 = ERR008: %1$s devrait trouver un nom de copybook après le verbe COPY dans <%2$s>.
ERR009 = ERR009: Un mot clé non défini <%1$s> a été rencontré lors de l'analyse d'une suite de tests.
INF001 = INF001: Essaiera de charger la configuration à partir de %1$s.
INF002 = INF002: La configuration a bien été chargée à partir de %1$s.
Original file line number Diff line number Diff line change
Expand Up @@ -7,5 +7,7 @@ ERR004 = ERR004: È previsto un argomento per l'opzione della riga di comando <%
ERR005 = ERR005: La stringa di specifica dell'opzione della riga di comando passata a GetOpt era null.
ERR006 = ERR006: Era prevista un'opzione della riga di comando, ma è stata ricevuta <%1$s>.
ERR007 = ERR007: Generator.runSuite () flusso di input vuoto (cobolSourceIn).
ERR008 = ERR008: %1$s dovrebbe trovare il nome di un quaderno dopo il verbo COPY in <%2$s>.
ERR009 = ERR009: È stata rilevata la parola chiave non definita <%1$s> durante l'analisi di una suite di test.
INF001 = INF001: Tentativo di caricare la configurazione da %1$s.
INF002 = INF002: Configurazione caricata correttamente da %1$s.
Original file line number Diff line number Diff line change
Expand Up @@ -7,5 +7,7 @@ ERR004 = ERR004: コマンドラインオプション<%1$s>の引数が必要で
ERR005 = ERR005: GetOptに渡されたコマンドラインオプション指定文字列がnullでした。
ERR006 = ERR006: コマンドラインオプションが必要ですが、<%1$s>を取得しました。
ERR007 = ERR007: Generator.runSuite()空の入力ストリーム(cobolSourceIn)。
ERR008 = ERR008: %1$sは、<%2$s>のCOPY動詞に続くコピーブック名を見つけると予想されます。
ERR009 = ERR009: テストスイートの解析中に、未定義のキーワード<%1$s>が検出されました。
INF001 = INF001: %1$sから構成を読み込もうとしています。
INF002 = INF002: 構成を%1$sから正常にロードしました。
Original file line number Diff line number Diff line change
Expand Up @@ -115,16 +115,23 @@ public void given_main_program_with_working_storage_it_inserts_test_copybooks_in

}

// @Test
// // We're asserting on computed hashes; this "test" gives us a readable version of the output file.
// public void see_the_merged_source_file_on_stdout() throws IOException {
// StringReader cobolSourceIn = makeCobolSourceProgram(cobolSourceWithoutWorkingStorage);
// StringWriter testSourceOut = new StringWriter();
// generator.mergeTestSuite(mockTestSuite, cobolSourceIn, testSourceOut);
// System.out.println("testSourceOut: ");
// System.out.println(testSourceOut.toString());
// }
@Test
public void given_main_program_with_working_storage_it_inserts_a_simple_test_suite() throws Exception {
Reader cobolSourceReader = new FileReader(testFile("MINIMAL-BEFORE-padded.CBL"));
BufferedReader reader = new BufferedReader(cobolSourceReader);
Writer mergedSourceWriter = new FileWriter(testFile("MERGEDSOURCE.CBL"));
generator.mergeTestSuite(new FileReader(testFile("MINIMAL-BEFORE-padded.CBL")),
cobolSourceReader,
mergedSourceWriter);
cobolSourceReader.close();
mergedSourceWriter.close();

String expectedHashValue = MD5.MD5HashFile(testFileName("MINIMAL-AFTER-padded.CBL"));
String actualHashValue = MD5.MD5HashFile(testFileName("MERGEDSOURCE.CBL"));
assertEquals(expectedHashValue, actualHashValue,
"Comparing expected file <" + testFileName("MINIMAL-AFTER-padded.CBL")
+ "> and actual file <" + testFileName("MERGEDSOURCE.CBL") + ">");
}

private File testFile(String fileName) {
File file = new File(pathToTestCobolSources + fileName);
Expand Down
48 changes: 48 additions & 0 deletions src/test/java/com/neopragma/cobolcheck/KeywordsTest.java
Original file line number Diff line number Diff line change
@@ -0,0 +1,48 @@
package com.neopragma.cobolcheck;

import org.junit.jupiter.params.ParameterizedTest;
import org.junit.jupiter.params.provider.Arguments;
import org.junit.jupiter.params.provider.MethodSource;

import java.util.List;
import java.util.stream.Stream;

import static org.junit.jupiter.api.Assertions.assertEquals;

public class KeywordsTest implements Constants {

@ParameterizedTest
@MethodSource("KeywordProvider")
public void it_returns_the_keyword_record_for_a_given_key(
String key,
String expectedKeywordValue,
List<String> expectedValidNextKey,
KeywordAction expectedKeywordAction) {
Keyword keyword = Keywords.getKeywordFor(key);
assertEquals(expectedKeywordValue, keyword.value());
assertEquals(expectedKeywordAction, keyword.keywordAction());
assertEquals(expectedValidNextKey, keyword.validNextKey());
}

private static Stream<Arguments> KeywordProvider() {
return Stream.of(
Arguments.of(EXPECT_KEYWORD, EXPECT_KEYWORD,
List.of(FIELDNAME_KEYWORD),
KeywordAction.ACTUAL_FIELDNAME),
Arguments.of(FIELDNAME_KEYWORD, EMPTY_STRING,
List.of(TO_BE_KEYWORD, NOT_KEYWORD),
KeywordAction.FIELDNAME),
Arguments.of(NOT_KEYWORD, NOT_KEYWORD,
List.of(TO_BE_KEYWORD),
KeywordAction.REVERSE_LOGIC),
Arguments.of(TO_BE_KEYWORD, TO_BE_KEYWORD,
List.of(FIELDNAME_KEYWORD,
ALPHANUMERIC_LITERAL_KEYWORD,
NUMERIC_LITERAL_KEYWORD,
TRUE,
FALSE),
KeywordAction.EXPECTED_VALUE)
);
}

}
Loading

0 comments on commit bc04310

Please sign in to comment.