From b62d21302a91edb924d4e683071e9830a333c3ba Mon Sep 17 00:00:00 2001 From: issacto Date: Fri, 18 Aug 2023 16:56:59 +0100 Subject: [PATCH] add test tree -1 Signed-off-by: issacto --- vs code extension/client/src/extension.ts | 179 +++++++++++++----- .../src/services/CobolCheckInputParser.ts | 41 ++-- .../client/src/services/TestTree.ts | 46 +++-- vs code extension/client/test.cut | 25 +++ .../client/testFixture copy/alpha.cut | 61 ++++++ .../client/testFixture copy/alpha/alpha.cut | 61 ++++++ .../client/testFixture copy/errorfree.cut | 25 +++ .../testFixture copy/missingdelimiters.cut | 11 ++ .../testFixture copy/missingtestsuite.cut | 18 ++ .../client/testFixture copy/syntaxerror.cut | 9 + .../testFixture/alpha/alpha copy/alpha.cut | 61 ++++++ .../client/testFixture/alpha/alpha.cut | 61 ++++++ .../client/testFixture/errorfree.cut | 5 + 13 files changed, 527 insertions(+), 76 deletions(-) create mode 100644 vs code extension/client/test.cut create mode 100644 vs code extension/client/testFixture copy/alpha.cut create mode 100644 vs code extension/client/testFixture copy/alpha/alpha.cut create mode 100644 vs code extension/client/testFixture copy/errorfree.cut create mode 100644 vs code extension/client/testFixture copy/missingdelimiters.cut create mode 100644 vs code extension/client/testFixture copy/missingtestsuite.cut create mode 100644 vs code extension/client/testFixture copy/syntaxerror.cut create mode 100644 vs code extension/client/testFixture/alpha/alpha copy/alpha.cut create mode 100644 vs code extension/client/testFixture/alpha/alpha.cut diff --git a/vs code extension/client/src/extension.ts b/vs code extension/client/src/extension.ts index e2193f5c..4c951d08 100644 --- a/vs code extension/client/src/extension.ts +++ b/vs code extension/client/src/extension.ts @@ -15,7 +15,7 @@ import { startCutLanguageClientServer, stopCutLanguageClientServer } from './ser import { ResultWebView } from './services/ResultWebView'; import { handleCobolCheckOut } from './Helpers/ExtensionHelper'; import path = require('path'); -import { getContentFromFilesystem, MarkdownTestData, TestCase, testData, TestFile } from "./services/testTree"; +import { getContentFromFilesystem, MarkdownTestData, TestCase, testData, TestFile, TestHeading } from "./services/TestTree"; let externalVsCodeInstallationDir = vscode.extensions.getExtension("openmainframeproject.cobol-check-extension").extensionPath; @@ -91,52 +91,62 @@ export function activate(context: ExtensionContext) { return startTestRun(request); } - const l = fileChangedEmitter.event(uri => startTestRun( + const l = fileChangedEmitter.event(uri => { + + return startTestRun( + new vscode.TestRunRequest2( [getOrCreateFile(ctrl, uri).file], undefined, request.profile, true ), - )); + )}); cancellation.onCancellationRequested(() => l.dispose()); }; const startTestRun = (request: vscode.TestRunRequest) => { - const queue: { test: vscode.TestItem; data: TestCase }[] = []; + const queue: { test: vscode.TestItem; data: TestCase | TestHeading }[] = []; const run = ctrl.createTestRun(request); // map of file uris to statements on each line: const coveredLines = new Map(); const discoverTests = async (tests: Iterable) => { - for (const test of tests) { - if (request.exclude?.includes(test)) { - continue; - } - - const data = testData.get(test); - if (data instanceof TestCase) { - run.enqueued(test); - queue.push({ test, data }); - } else { - if (data instanceof TestFile && !data.didResolve) { - await data.updateFromDisk(ctrl, test); + if(tests){ + for (const test of tests) { + if (request.exclude?.includes(test)) { + continue; } - await discoverTests(gatherTestItems(test.children)); - } + const data = testData.get(test); + if (data instanceof TestCase + || (data instanceof TestHeading && test.children.size==0) + ) { + run.enqueued(test); + queue.push({ test, data }); + } else { + if (data instanceof TestFile ) { + await data.updateFromDisk(ctrl, test); + } + + await discoverTests(gatherTestItems(test)); + } - if (test.uri && !coveredLines.has(test.uri.toString())) { - try { - const lines = (await getContentFromFilesystem(test.uri)).split('\n'); - coveredLines.set( - test.uri.toString(), - lines.map((lineText, lineNo) => - lineText.trim().length ? new vscode.StatementCoverage(0, new vscode.Position(lineNo, 0)) : undefined - ) - ); - } catch { - // ignored + if (test.uri && !coveredLines.has(test.uri.toString())) { + try { + const lines = (await getContentFromFilesystem(test.uri,true)) + if(lines!=""){ + const lineArr = lines.split('\n'); + coveredLines.set( + test.uri.toString(), + lineArr.map((lineText, lineNo) => + lineText.trim().length ? new vscode.StatementCoverage(0, new vscode.Position(lineNo, 0)) : undefined + ) + ); + } + } catch { + // ignored + } } } } @@ -151,7 +161,7 @@ export function activate(context: ExtensionContext) { run.started(test); await data.run(test, run); } - + const lineNo = test.range!.start.line; const fileCoverage = coveredLines.get(test.uri!.toString()); if (fileCoverage) { @@ -160,7 +170,6 @@ export function activate(context: ExtensionContext) { run.appendOutput(`Completed ${test.id}\r\n`); } - run.end(); }; @@ -180,7 +189,7 @@ export function activate(context: ExtensionContext) { }, }; - discoverTests(request.include ?? gatherTestItems(ctrl.items)).then(runTestQueue); + discoverTests(request.include ?? gatherTestItemsFromCollection(ctrl.items)).then(runTestQueue); }; ctrl.refreshHandler = async () => { @@ -205,7 +214,6 @@ export function activate(context: ExtensionContext) { if (e.uri.scheme !== 'file') { return; } - if (!e.uri.path.endsWith('.cut')) { return; } @@ -228,26 +236,108 @@ export function deactivate() { stopCutLanguageClientServer(); } +function createDirItems( controller:vscode.TestController, uri: vscode.Uri){ + + const dirArr = vscode.workspace.asRelativePath(uri.fsPath).split("/") + const rootDir = uri.fsPath.replace(vscode.workspace.asRelativePath(uri.fsPath),"") + const rootUri = rootDir+dirArr[0] + let tmpUri = vscode.Uri.file(rootUri); + + var file :vscode.TestItem = null; + controller.createTestItem + var data = null + if(!controller.items.get(rootUri)){ + file = controller.createTestItem(rootUri, dirArr[0], tmpUri); + controller.items.add(file); + data = new TestFile() + testData.set(file, data); + file.canResolveChildren = true; + } + else{ + file = controller.items.get(rootUri) + data = testData.get(file) + } + + + var prevFile: vscode.TestItem = file + var tmpDir = rootUri + + for(var i =1;i {items=items.concat(gatherTestItems(item))}); + return items; + } + else if(data instanceof TestHeading && !test.children){ + items.push(test) + return items; + }else if(data instanceof TestHeading && test.children){ + test.children.forEach(item => items.push(item)); + return items; + } + else if(data instanceof TestCase){ + items.push(test); + return items; + } + return items; - file.canResolveChildren = true; - return { file, data }; } -function gatherTestItems(collection: vscode.TestItemCollection) { - const items: vscode.TestItem[] = []; - collection.forEach(item => items.push(item)); +function gatherTestItemsFromCollection(collection: vscode.TestItemCollection) { + var items: vscode.TestItem[] = []; + collection.forEach(item => { + items = items.concat(gatherTestItems(item)) + }); return items; } @@ -270,6 +360,7 @@ async function findInitialFiles(controller: vscode.TestController, pattern: vsco function startWatchingWorkspace(controller: vscode.TestController, fileChangedEmitter: vscode.EventEmitter ) { return getWorkspaceTestPatterns().map(({ workspaceFolder, pattern }) => { + const watcher = vscode.workspace.createFileSystemWatcher(pattern); watcher.onDidCreate(uri => { diff --git a/vs code extension/client/src/services/CobolCheckInputParser.ts b/vs code extension/client/src/services/CobolCheckInputParser.ts index 64ef822d..27311aa9 100644 --- a/vs code extension/client/src/services/CobolCheckInputParser.ts +++ b/vs code extension/client/src/services/CobolCheckInputParser.ts @@ -8,27 +8,30 @@ export const parseMarkdown = (text: string, events: { onTest(range: vscode.Range, name: string): void; onHeading(range: vscode.Range, name: string, depth: number): void; }) => { - const lines = text.split('\n'); - - for (let lineNo = 0; lineNo < lines.length; lineNo++) { - const line = lines[lineNo]; - - const testCase = testCaseRegex.exec(line); - if (testCase) { - var [,pounds, name] = testCase; - name = name.replace(/['"]+/g, ''); - const range = new vscode.Range(new vscode.Position(lineNo, 0), new vscode.Position(lineNo, testCase[0].length)); - events.onTest(range, name); - continue; - } + if(text!=null){ - const testSuite = testSuiteRegex.exec(line); - if (testSuite) { - var [,pounds, name] = testSuite; - name = name.replace(/['"]+/g, ''); - const range = new vscode.Range(new vscode.Position(lineNo, line.indexOf(pounds)), new vscode.Position(lineNo, line.indexOf(name) + name.length)); - events.onHeading(range, name, 1); + const lines = text.split('\n'); + for (let lineNo = 0; lineNo < lines.length; lineNo++) { + const line = lines[lineNo]; + + const testCase = testCaseRegex.exec(line); + if (testCase) { + var [,pounds, name] = testCase; + name = name.replace(/['"]+/g, ''); + const range = new vscode.Range(new vscode.Position(lineNo, 0), new vscode.Position(lineNo, testCase[0].length)); + events.onTest(range, name); + continue; + } + + + const testSuite = testSuiteRegex.exec(line); + if (testSuite) { + var [,pounds, name] = testSuite; + name = name.replace(/['"]+/g, ''); + const range = new vscode.Range(new vscode.Position(lineNo, line.indexOf(pounds)), new vscode.Position(lineNo, line.indexOf(name) + name.length)); + events.onHeading(range, name, 1); + } } } }; diff --git a/vs code extension/client/src/services/TestTree.ts b/vs code extension/client/src/services/TestTree.ts index bab55d08..25d4cd32 100644 --- a/vs code extension/client/src/services/TestTree.ts +++ b/vs code extension/client/src/services/TestTree.ts @@ -1,19 +1,27 @@ import { TextDecoder } from 'util'; import * as vscode from 'vscode'; import { parseMarkdown } from './CobolCheckInputParser'; +import internal = require('stream'); +import { integer } from 'vscode-languageclient'; const textDecoder = new TextDecoder('utf-8'); export type MarkdownTestData = TestFile | TestHeading | TestCase; +// only for the root files export const testData = new WeakMap(); let generationCounter = 0; -export const getContentFromFilesystem = async (uri: vscode.Uri) => { +export const getContentFromFilesystem = async (uri: vscode.Uri, isFile) => { try { - const rawContent = await vscode.workspace.fs.readFile(uri); - return textDecoder.decode(rawContent); + // vscode.workspace.fs.readDirectory + if(isFile){ + const rawContent = await vscode.workspace.fs.readFile(uri); + return textDecoder.decode(rawContent); + } + return null + } catch (e) { console.warn(`Error providing tests for ${uri.fsPath}`, e); return ''; @@ -25,9 +33,11 @@ export class TestFile { public async updateFromDisk(controller: vscode.TestController, item: vscode.TestItem) { try { - const content = await getContentFromFilesystem(item.uri!); - item.error = undefined; - this.updateFromContents(controller, content, item); + if(item.children.size==0){ + var content= await getContentFromFilesystem(item.uri!, (item.children.size==0)); + item.error = undefined; + this.updateFromContents(controller, content, item, item.children.size); + } } catch (e) { item.error = (e as Error).stack; } @@ -37,7 +47,7 @@ export class TestFile { * Parses the tests from the input text, and updates the tests contained * by this file to be those from the text, */ - public updateFromContents(controller: vscode.TestController, content: string, item: vscode.TestItem) { + public updateFromContents(controller: vscode.TestController, content: string, item: vscode.TestItem, fileDepth: integer) { const ancestors = [{ item, children: [] as vscode.TestItem[] }]; const thisGeneration = generationCounter++; this.didResolve = true; @@ -48,14 +58,12 @@ export class TestFile { finished.item.children.replace(finished.children); } }; - + parseMarkdown(content, { onTest: (range, label) => { const parent = ancestors[ancestors.length - 1]; const data = new TestCase(label); const id = `${item.uri}/${data.getLabel()}`; - - const tcase = controller.createTestItem(id, data.getLabel(), item.uri); testData.set(tcase, data); tcase.range = range; @@ -66,7 +74,6 @@ export class TestFile { ascend(depth); const parent = ancestors[ancestors.length - 1]; const id = `${item.uri}/${name}`; - const thead = controller.createTestItem(id, name, item.uri); thead.range = range; testData.set(thead, new TestHeading(thisGeneration)); @@ -75,12 +82,24 @@ export class TestFile { }, }); - ascend(0); // finish and assign children for all remaining items + ascend(fileDepth) + // if(isFile) ascend(1) + // else ascend(0) // finish and assign children for all remaining items } + + + } export class TestHeading { - constructor(public generation: number) { } + constructor(public generation: number) { + } + async run(item: vscode.TestItem, options: vscode.TestRun): Promise { + const start = Date.now(); + await new Promise(resolve => setTimeout(resolve, 1000 + Math.random() * 1000)); + const duration = Date.now() - start; + options.passed(item, duration); + } } type Operator = '+' | '-' | '*' | '/'; @@ -127,3 +146,4 @@ export class TestCase { // } // } } + diff --git a/vs code extension/client/test.cut b/vs code extension/client/test.cut new file mode 100644 index 00000000..261f924f --- /dev/null +++ b/vs code extension/client/test.cut @@ -0,0 +1,25 @@ + TESTSUITE 'Test AARM503 sections' + + TestCase "Equality with an alphanumeric literal using TO BE" + move "value1" to ws-field-1 + Expect ws-field-1 to be "value1" + + + BEFORE-EACH + MOVE 0 TO STATU-KD IN AARM503-PARM + END-BEFORE + + MOCK SECTION 911-PUT-HARD-ERROR + CONTINUE + END-MOCK + + MOCK PARAGRAPH 300-CHANGE-1 + EVALUATE VALUE-1 + WHEN "Hello" + MOVE "MOCKED" TO VALUE-1 + WHEN OTHER + MOVE "mocked" TO VALUE-1 + END-EVALUATE + END-MOCK + + \ No newline at end of file diff --git a/vs code extension/client/testFixture copy/alpha.cut b/vs code extension/client/testFixture copy/alpha.cut new file mode 100644 index 00000000..8074bb50 --- /dev/null +++ b/vs code extension/client/testFixture copy/alpha.cut @@ -0,0 +1,61 @@ + TestSuite "Tests of alphanumeric expectations" + + TestCase "Equality with an alphanumeric literal using TO BE" + move "value1" to ws-field-1 + Expect ws-field-1 to be "value1" + + TestCase "Equality with an alphanumeric literal using TO EQUAL" + move "value2" to ws-field-1 + Expect ws-field-1 to equal "value2" + + TestCase "Equality with an alphanumeric literal using '='" + move "value3" to ws-field-1 + Expect ws-field-1 = "value3" + + TestCase "Equality with an alphanumeric literal and reference modification" + move "Hello, World!" to ws-field-2 + Expect ws-field-2(8:5) to be "World" + + TestCase "Non-equality with an alphanumeric literal using TO BE" + move "value4" to ws-field-1 + Expect ws-field-1 not to be "value1" + + TestCase "Non-equality with an alphanumeric literal using TO EQUAL" + move "value5" to ws-field-1 + Expect ws-field-1 not to equal "value1" + + TestCase "Non-equality with an alphanumeric literal using '!='" + move "value6" to ws-field-1 + Expect ws-field-1 != "value1" + + TestCase "Non-equality with an alphanumeric literal and reference modification" + move "Hello, World!" to ws-field-2 + Expect ws-field-2(8:6) not to be "World" + + TestCase "Greater-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-1 > ws-field-2 + + TestCase "Less-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-2 < ws-field-1 + + TestCase "Not greater-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-2 not > ws-field-1 + + TestCase "Not less-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-1 not < ws-field-2 + + TestCase "Display numeric" + move 6 to ws-display-numeric + expect ws-display-numeric to be 6 + + + + diff --git a/vs code extension/client/testFixture copy/alpha/alpha.cut b/vs code extension/client/testFixture copy/alpha/alpha.cut new file mode 100644 index 00000000..8074bb50 --- /dev/null +++ b/vs code extension/client/testFixture copy/alpha/alpha.cut @@ -0,0 +1,61 @@ + TestSuite "Tests of alphanumeric expectations" + + TestCase "Equality with an alphanumeric literal using TO BE" + move "value1" to ws-field-1 + Expect ws-field-1 to be "value1" + + TestCase "Equality with an alphanumeric literal using TO EQUAL" + move "value2" to ws-field-1 + Expect ws-field-1 to equal "value2" + + TestCase "Equality with an alphanumeric literal using '='" + move "value3" to ws-field-1 + Expect ws-field-1 = "value3" + + TestCase "Equality with an alphanumeric literal and reference modification" + move "Hello, World!" to ws-field-2 + Expect ws-field-2(8:5) to be "World" + + TestCase "Non-equality with an alphanumeric literal using TO BE" + move "value4" to ws-field-1 + Expect ws-field-1 not to be "value1" + + TestCase "Non-equality with an alphanumeric literal using TO EQUAL" + move "value5" to ws-field-1 + Expect ws-field-1 not to equal "value1" + + TestCase "Non-equality with an alphanumeric literal using '!='" + move "value6" to ws-field-1 + Expect ws-field-1 != "value1" + + TestCase "Non-equality with an alphanumeric literal and reference modification" + move "Hello, World!" to ws-field-2 + Expect ws-field-2(8:6) not to be "World" + + TestCase "Greater-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-1 > ws-field-2 + + TestCase "Less-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-2 < ws-field-1 + + TestCase "Not greater-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-2 not > ws-field-1 + + TestCase "Not less-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-1 not < ws-field-2 + + TestCase "Display numeric" + move 6 to ws-display-numeric + expect ws-display-numeric to be 6 + + + + diff --git a/vs code extension/client/testFixture copy/errorfree.cut b/vs code extension/client/testFixture copy/errorfree.cut new file mode 100644 index 00000000..261f924f --- /dev/null +++ b/vs code extension/client/testFixture copy/errorfree.cut @@ -0,0 +1,25 @@ + TESTSUITE 'Test AARM503 sections' + + TestCase "Equality with an alphanumeric literal using TO BE" + move "value1" to ws-field-1 + Expect ws-field-1 to be "value1" + + + BEFORE-EACH + MOVE 0 TO STATU-KD IN AARM503-PARM + END-BEFORE + + MOCK SECTION 911-PUT-HARD-ERROR + CONTINUE + END-MOCK + + MOCK PARAGRAPH 300-CHANGE-1 + EVALUATE VALUE-1 + WHEN "Hello" + MOVE "MOCKED" TO VALUE-1 + WHEN OTHER + MOVE "mocked" TO VALUE-1 + END-EVALUATE + END-MOCK + + \ No newline at end of file diff --git a/vs code extension/client/testFixture copy/missingdelimiters.cut b/vs code extension/client/testFixture copy/missingdelimiters.cut new file mode 100644 index 00000000..d4725ee7 --- /dev/null +++ b/vs code extension/client/testFixture copy/missingdelimiters.cut @@ -0,0 +1,11 @@ + TESTSUITE 'Test AARM503 sections' + + BEFORE-EACH + MOVE 0 TO STATU-KD IN AARM503-PARM + END-BEFORE + + MOCK SECTION 911-PUT-HARD-ERROR + CONTINUE + END-MOCK + + \ No newline at end of file diff --git a/vs code extension/client/testFixture copy/missingtestsuite.cut b/vs code extension/client/testFixture copy/missingtestsuite.cut new file mode 100644 index 00000000..eb9df9b8 --- /dev/null +++ b/vs code extension/client/testFixture copy/missingtestsuite.cut @@ -0,0 +1,18 @@ + TESTSUITE 'Test AARM503 sections' + + BEFORE-EACH + MOVE 0 TO STATU-KD IN AARM503-PARM + END-BEFORE + + MOCK SECTION 911-PUT-HARD-ERROR + CONTINUE + END-MOCK + + BEFORE-EACH + MOVE 0 TO STATU-KD IN AARM503-PARM + END-BEFORE + + MOCK SECTION 911-PUT-HARD-ERROR + CONTINUE + END-MOCK + \ No newline at end of file diff --git a/vs code extension/client/testFixture copy/syntaxerror.cut b/vs code extension/client/testFixture copy/syntaxerror.cut new file mode 100644 index 00000000..1f59ed77 --- /dev/null +++ b/vs code extension/client/testFixture copy/syntaxerror.cut @@ -0,0 +1,9 @@ + TESTSUITE 'Test AARM503 sections' + TESTSUITE 'Test AARM504 sections' + BEFORE-EACH + MOV 0 TO STATU-KD IN AARM503-PARM + END-BEFORE + + MOCK SECTION 911-PUT-HARD-ERROR + CONTINUE + END-MOCK diff --git a/vs code extension/client/testFixture/alpha/alpha copy/alpha.cut b/vs code extension/client/testFixture/alpha/alpha copy/alpha.cut new file mode 100644 index 00000000..8074bb50 --- /dev/null +++ b/vs code extension/client/testFixture/alpha/alpha copy/alpha.cut @@ -0,0 +1,61 @@ + TestSuite "Tests of alphanumeric expectations" + + TestCase "Equality with an alphanumeric literal using TO BE" + move "value1" to ws-field-1 + Expect ws-field-1 to be "value1" + + TestCase "Equality with an alphanumeric literal using TO EQUAL" + move "value2" to ws-field-1 + Expect ws-field-1 to equal "value2" + + TestCase "Equality with an alphanumeric literal using '='" + move "value3" to ws-field-1 + Expect ws-field-1 = "value3" + + TestCase "Equality with an alphanumeric literal and reference modification" + move "Hello, World!" to ws-field-2 + Expect ws-field-2(8:5) to be "World" + + TestCase "Non-equality with an alphanumeric literal using TO BE" + move "value4" to ws-field-1 + Expect ws-field-1 not to be "value1" + + TestCase "Non-equality with an alphanumeric literal using TO EQUAL" + move "value5" to ws-field-1 + Expect ws-field-1 not to equal "value1" + + TestCase "Non-equality with an alphanumeric literal using '!='" + move "value6" to ws-field-1 + Expect ws-field-1 != "value1" + + TestCase "Non-equality with an alphanumeric literal and reference modification" + move "Hello, World!" to ws-field-2 + Expect ws-field-2(8:6) not to be "World" + + TestCase "Greater-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-1 > ws-field-2 + + TestCase "Less-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-2 < ws-field-1 + + TestCase "Not greater-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-2 not > ws-field-1 + + TestCase "Not less-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-1 not < ws-field-2 + + TestCase "Display numeric" + move 6 to ws-display-numeric + expect ws-display-numeric to be 6 + + + + diff --git a/vs code extension/client/testFixture/alpha/alpha.cut b/vs code extension/client/testFixture/alpha/alpha.cut new file mode 100644 index 00000000..8074bb50 --- /dev/null +++ b/vs code extension/client/testFixture/alpha/alpha.cut @@ -0,0 +1,61 @@ + TestSuite "Tests of alphanumeric expectations" + + TestCase "Equality with an alphanumeric literal using TO BE" + move "value1" to ws-field-1 + Expect ws-field-1 to be "value1" + + TestCase "Equality with an alphanumeric literal using TO EQUAL" + move "value2" to ws-field-1 + Expect ws-field-1 to equal "value2" + + TestCase "Equality with an alphanumeric literal using '='" + move "value3" to ws-field-1 + Expect ws-field-1 = "value3" + + TestCase "Equality with an alphanumeric literal and reference modification" + move "Hello, World!" to ws-field-2 + Expect ws-field-2(8:5) to be "World" + + TestCase "Non-equality with an alphanumeric literal using TO BE" + move "value4" to ws-field-1 + Expect ws-field-1 not to be "value1" + + TestCase "Non-equality with an alphanumeric literal using TO EQUAL" + move "value5" to ws-field-1 + Expect ws-field-1 not to equal "value1" + + TestCase "Non-equality with an alphanumeric literal using '!='" + move "value6" to ws-field-1 + Expect ws-field-1 != "value1" + + TestCase "Non-equality with an alphanumeric literal and reference modification" + move "Hello, World!" to ws-field-2 + Expect ws-field-2(8:6) not to be "World" + + TestCase "Greater-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-1 > ws-field-2 + + TestCase "Less-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-2 < ws-field-1 + + TestCase "Not greater-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-2 not > ws-field-1 + + TestCase "Not less-than sign with an alphanumeric literal" + move "Beta" to ws-field-1 + move "Alpha" to ws-field-2 + Expect ws-field-1 not < ws-field-2 + + TestCase "Display numeric" + move 6 to ws-display-numeric + expect ws-display-numeric to be 6 + + + + diff --git a/vs code extension/client/testFixture/errorfree.cut b/vs code extension/client/testFixture/errorfree.cut index d91c7f27..261f924f 100644 --- a/vs code extension/client/testFixture/errorfree.cut +++ b/vs code extension/client/testFixture/errorfree.cut @@ -1,5 +1,10 @@ TESTSUITE 'Test AARM503 sections' + TestCase "Equality with an alphanumeric literal using TO BE" + move "value1" to ws-field-1 + Expect ws-field-1 to be "value1" + + BEFORE-EACH MOVE 0 TO STATU-KD IN AARM503-PARM END-BEFORE