Skip to content

Commit 3f8357a

Browse files
authored
WI #2735 Externalize completion logic into a testable processor (#2742)
1 parent 2c3331d commit 3f8357a

File tree

7 files changed

+312
-140
lines changed

7 files changed

+312
-140
lines changed
Lines changed: 47 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,47 @@
1+
IDENTIFICATION DIVISION.
2+
PROGRAM-ID. TCOMFL06.
3+
DATA DIVISION.
4+
WORKING-STORAGE SECTION.
5+
01 var1 PIC X.
6+
01 other-data PIC X.
7+
01 var2 PIC 9.
8+
PROCEDURE DIVISION.
9+
DISPLAY v
10+
GOBACK
11+
.
12+
END PROGRAM TCOMFL06.
13+
---------------------------------------------------------------------------------
14+
{"line":8,"character":20}
15+
---------------------------------------------------------------------------------
16+
[
17+
{
18+
"label": "var1 (Alphanumeric) (var1)",
19+
"kind": 6,
20+
"insertText": "var1",
21+
"data": {
22+
"start": {
23+
"line": 8,
24+
"character": 19
25+
},
26+
"end": {
27+
"line": 8,
28+
"character": 20
29+
}
30+
}
31+
},
32+
{
33+
"label": "var2 (Numeric) (var2)",
34+
"kind": 6,
35+
"insertText": "var2",
36+
"data": {
37+
"start": {
38+
"line": 8,
39+
"character": 19
40+
},
41+
"end": {
42+
"line": 8,
43+
"character": 20
44+
}
45+
}
46+
}
47+
]
Lines changed: 66 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,66 @@
1+
using System.Diagnostics;
2+
using System.Runtime.CompilerServices;
3+
using Microsoft.VisualStudio.TestTools.UnitTesting;
4+
using Newtonsoft.Json;
5+
using TypeCobol.LanguageServer.Test.Utilities;
6+
using TypeCobol.Test.Utils;
7+
using TypeCobol.Test;
8+
using TypeCobol.Compiler.Directives;
9+
using TypeCobol.Compiler;
10+
using TypeCobol.LanguageServer.Processor;
11+
using Newtonsoft.Json.Linq;
12+
using TypeCobol.LanguageServer.VsCodeProtocol;
13+
14+
namespace TypeCobol.LanguageServer.Test.ProcessorTests
15+
{
16+
[TestClass]
17+
public class CompletionProcessorTest
18+
{
19+
private const string RELATIVE_PATH = "Completion";
20+
private const string ROOT_PATH = "ProcessorTests";
21+
22+
/*
23+
* Using a blank context as it is required by the processor but it won't matter during the tests
24+
* as each test is independent.
25+
*/
26+
protected readonly CompletionProcessor _processor = new(new SignatureCompletionContext());
27+
28+
private void ExecuteTest([CallerMemberName] string sourceFileName = null)
29+
{
30+
Debug.Assert(sourceFileName != null);
31+
32+
// Parse test data file
33+
var folder = PlatformUtils.GetPathForProjectFile(RELATIVE_PATH, Path.GetFullPath(ROOT_PATH));
34+
var testDataFilePath = $"{Path.Combine(folder, sourceFileName)}.txt";
35+
var testData = LanguageServerTestUtils.ParseMultiplePartsContent(testDataFilePath);
36+
Debug.Assert(testData.Count == 3);
37+
string cobolString = testData[0];
38+
string completionRequest = testData[1];
39+
string expectedProposals = testData[2];
40+
41+
// Parse original source code
42+
var options = new TypeCobolOptions();
43+
var format = DocumentFormat.RDZReferenceFormat;
44+
/*
45+
* Assuming the source code is not part of a copy. Testing completion inside a copy
46+
* is not very meaningful as they are usually made of data definitions only.
47+
*/
48+
var compilationUnit = ParserUtils.ParseCobolString(cobolString, false, options, format);
49+
50+
// Get completion request argument (single arg is Position)
51+
var position = JToken.Parse(completionRequest).ToObject<Position>();
52+
53+
// Execute processor and build actual result
54+
var completionItems = _processor.ComputeProposals(compilationUnit, position);
55+
string actualProposals = JToken.FromObject(completionItems, new JsonSerializer() { NullValueHandling = NullValueHandling.Ignore })
56+
.ToString(Formatting.Indented)
57+
+ Environment.NewLine;
58+
59+
// Compare to expected
60+
TestUtils.CompareContent(sourceFileName, actualProposals, expectedProposals);
61+
}
62+
63+
[TestMethod]
64+
public void SimpleCompletionForVariable() => ExecuteTest();
65+
}
66+
}

TypeCobol.LanguageServer/Completion Factory/CompletionFactoryHelpers.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -188,9 +188,8 @@ public static List<CompletionItem> CreateCompletionItemsForProcedures(IEnumerabl
188188
((object[])completionItem.data)[1] = signatureInformation;
189189

190190
//Store the link between the hash and the procedure. This will help to determine the procedure parameter completion context later.
191-
if (!functionDeclarationSignatureDictionary.ContainsKey(signatureInformation))
191+
if (functionDeclarationSignatureDictionary.TryAdd(signatureInformation, proc))
192192
{
193-
functionDeclarationSignatureDictionary.Add(signatureInformation, proc);
194193
completionItems.Add(completionItem);
195194
}
196195
}
Lines changed: 144 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,144 @@
1+
using TypeCobol.Compiler;
2+
using TypeCobol.Compiler.CodeElements;
3+
using TypeCobol.Compiler.Nodes;
4+
using TypeCobol.Compiler.Scanner;
5+
using TypeCobol.LanguageServer.VsCodeProtocol;
6+
7+
using Range = TypeCobol.LanguageServer.VsCodeProtocol.Range;
8+
9+
namespace TypeCobol.LanguageServer.Processor
10+
{
11+
public class CompletionProcessor
12+
{
13+
private readonly SignatureCompletionContext _signatureCompletionContext;
14+
15+
public CompletionProcessor(SignatureCompletionContext signatureCompletionContext)
16+
{
17+
_signatureCompletionContext = signatureCompletionContext;
18+
}
19+
20+
public List<CompletionItem> ComputeProposals(CompilationUnit compilationUnit, Position position)
21+
{
22+
List<CompletionItem> items;
23+
24+
var wrappedCodeElements = TypeCobolServer.CodeElementFinder(compilationUnit, position);
25+
if (wrappedCodeElements == null)
26+
return null;
27+
28+
//Try to get a significant token for completion and return the codeelement containing the matching token.
29+
CodeElement matchingCodeElement = CodeElementMatcher.MatchCompletionCodeElement(position,
30+
wrappedCodeElements,
31+
out var userFilterToken, out var lastSignificantToken); //Magic happens here
32+
33+
if (lastSignificantToken != null)
34+
{
35+
36+
switch (lastSignificantToken.TokenType)
37+
{
38+
case TokenType.PERFORM:
39+
items = new CompletionAfterPerform(userFilterToken).ComputeProposals(compilationUnit, matchingCodeElement);
40+
break;
41+
case TokenType.CALL:
42+
_signatureCompletionContext.Candidates.Clear(); //Clear to avoid key collision
43+
items = new CompletionForProcedure(userFilterToken, _signatureCompletionContext.Candidates).ComputeProposals(compilationUnit, matchingCodeElement);
44+
items.AddRange(new CompletionForLibrary(userFilterToken).ComputeProposals(compilationUnit, matchingCodeElement));
45+
break;
46+
case TokenType.TYPE:
47+
items = new CompletionForType(userFilterToken).ComputeProposals(compilationUnit, matchingCodeElement);
48+
items.AddRange(new CompletionForLibrary(userFilterToken).ComputeProposals(compilationUnit, matchingCodeElement));
49+
break;
50+
case TokenType.QualifiedNameSeparator:
51+
items = new CompletionForQualifiedName(userFilterToken, lastSignificantToken, position, _signatureCompletionContext.Candidates).ComputeProposals(compilationUnit, matchingCodeElement);
52+
break;
53+
case TokenType.INPUT:
54+
case TokenType.OUTPUT:
55+
case TokenType.IN_OUT:
56+
items = new CompletionForProcedureParameter(userFilterToken, lastSignificantToken, position, _signatureCompletionContext.BestMatch).ComputeProposals(compilationUnit, matchingCodeElement);
57+
break;
58+
case TokenType.DISPLAY:
59+
Predicate<DataDefinition> excludeNonDisplayable = dataDefinition =>
60+
dataDefinition.Usage != DataUsage.ProcedurePointer // invalid usages in DISPLAY statement
61+
&& dataDefinition.Usage != DataUsage.FunctionPointer
62+
&& dataDefinition.Usage != DataUsage.ObjectReference
63+
&& dataDefinition.Usage != DataUsage.Index
64+
&& dataDefinition.CodeElement?.LevelNumber != null
65+
&& dataDefinition.CodeElement.LevelNumber.Value < 88;
66+
// Ignore level 88. Note that dataDefinition.CodeElement != null condition also filters out IndexDefinition which is invalid in the context of DISPLAY
67+
// Filtering dataDefinition without LevelNumber also excludes FileDescription which are invalid for a DISPLAY
68+
items = new CompletionForVariable(userFilterToken, excludeNonDisplayable).ComputeProposals(compilationUnit, matchingCodeElement);
69+
break;
70+
case TokenType.MOVE:
71+
Predicate<DataDefinition> excludeLevel88 = dataDefinition =>
72+
(dataDefinition.CodeElement?.LevelNumber != null && dataDefinition.CodeElement.LevelNumber.Value < 88)
73+
||
74+
(dataDefinition.CodeElement == null && dataDefinition is IndexDefinition);
75+
//Ignore 88 level variable
76+
items = new CompletionForVariable(userFilterToken, excludeLevel88).ComputeProposals(compilationUnit, matchingCodeElement);
77+
break;
78+
case TokenType.TO:
79+
items = new CompletionForTo(userFilterToken, lastSignificantToken).ComputeProposals(compilationUnit, matchingCodeElement);
80+
break;
81+
case TokenType.INTO:
82+
Predicate<DataDefinition> onlyAlpha = dataDefinition => dataDefinition.CodeElement != null &&
83+
(dataDefinition.DataType == DataType.Alphabetic ||
84+
dataDefinition.DataType == DataType.Alphanumeric ||
85+
dataDefinition.DataType == DataType.AlphanumericEdited);
86+
items = new CompletionForVariable(userFilterToken, onlyAlpha).ComputeProposals(compilationUnit, matchingCodeElement);
87+
break;
88+
case TokenType.SET:
89+
Predicate<DataDefinition> keepCompatibleTypes = dataDefinition => dataDefinition.CodeElement?.Type == CodeElementType.DataConditionEntry //Level 88 Variable
90+
|| dataDefinition.DataType == DataType.Numeric //Numeric Integer Variable
91+
|| dataDefinition.Usage == DataUsage.Pointer
92+
|| dataDefinition.Usage == DataUsage.Pointer32; //Or usage is pointer/pointer-32
93+
items = new CompletionForVariable(userFilterToken, keepCompatibleTypes).ComputeProposals(compilationUnit, matchingCodeElement);
94+
break;
95+
case TokenType.OF:
96+
items = new CompletionForOf(userFilterToken, position).ComputeProposals(compilationUnit, matchingCodeElement);
97+
break;
98+
default:
99+
// Unable to suggest anything
100+
items = new List<CompletionItem>();
101+
break;
102+
}
103+
}
104+
else
105+
{
106+
//If no known keyword has been found, let's try to get the context and return available variables.
107+
if (matchingCodeElement == null && wrappedCodeElements.Any())
108+
{
109+
userFilterToken =
110+
wrappedCodeElements.First().ArrangedConsumedTokens.FirstOrDefault(
111+
t =>
112+
position.character <= t.StopIndex + 1 && position.character > t.StartIndex
113+
&& t.Line == position.line + 1
114+
&& t.TokenType == TokenType.UserDefinedWord); //Get the userFilterToken to filter the results
115+
items = new CompletionForVariable(userFilterToken, _ => true).ComputeProposals(compilationUnit, wrappedCodeElements.First());
116+
}
117+
else
118+
{
119+
//Return a default text to inform the user that completion is not available after the given token
120+
items = new List<CompletionItem>(1)
121+
{
122+
new CompletionItem() { label = "Completion is not available in this context", insertText = string.Empty }
123+
};
124+
}
125+
}
126+
127+
if (userFilterToken != null)
128+
{
129+
//Add the range object to let the client know the position of the user filter token
130+
var range = Range.FromPositions(userFilterToken.Line - 1, userFilterToken.StartIndex, userFilterToken.Line - 1, userFilterToken.StopIndex + 1);
131+
//-1 on line to 0 based / +1 on stop index to include the last character
132+
items.ForEach(c =>
133+
{
134+
if (c.data != null && c.data.GetType().IsArray)
135+
((object[])c.data)[0] = range;
136+
else
137+
c.data = range;
138+
});
139+
}
140+
141+
return items;
142+
}
143+
}
144+
}
Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,28 @@
1+
using TypeCobol.Compiler.Nodes;
2+
using TypeCobol.LanguageServer.VsCodeProtocol;
3+
4+
namespace TypeCobol.LanguageServer
5+
{
6+
/// <summary>
7+
/// Keeps track of current signature completion context.
8+
///
9+
/// Candidates for signature completion are selected explicitly using a "textDocument/signatureHelp" request
10+
/// or implicitly during completion request after a CALL keyword.
11+
/// The best match for signature completion is either selected directly by the client when multiple
12+
/// procedures are available or automatically set when a single procedure is available.
13+
/// Finally the best match procedure is used to provide results when completion is requested
14+
/// after INPUT or IN-OUT or OUTPUT TypeCobol keywords.
15+
/// </summary>
16+
public class SignatureCompletionContext
17+
{
18+
public Dictionary<SignatureInformation, FunctionDeclaration> Candidates { get; }
19+
20+
public FunctionDeclaration BestMatch { get; set; }
21+
22+
public SignatureCompletionContext()
23+
{
24+
Candidates = new Dictionary<SignatureInformation, FunctionDeclaration>();
25+
BestMatch = null;
26+
}
27+
}
28+
}

TypeCobol.LanguageServer/TypeCobolCustomLanguageServer/TypeCobolCustomLanguageServer.cs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -343,16 +343,16 @@ protected virtual void OnDidReceiveSignatureHelpContext(SignatureHelpContextPara
343343
if (parameters?.signatureInformation == null) //Means that the client leave the context
344344
{
345345
//Make the context signature completion null
346-
this.SignatureCompletionContext = null;
346+
this.SignatureCompletionContext.BestMatch = null;
347347
//Clean up the dictionary
348-
this.FunctionDeclarations.Clear();
348+
this.SignatureCompletionContext.Candidates.Clear();
349349
return;
350350
}
351351

352-
var retrievedFuncDeclarationPair = this.FunctionDeclarations.FirstOrDefault(item => item.Key.Equals(parameters.signatureInformation));
353-
354-
if (retrievedFuncDeclarationPair.Key != null)
355-
this.SignatureCompletionContext = retrievedFuncDeclarationPair.Value;
352+
if (this.SignatureCompletionContext.Candidates.TryGetValue(parameters.signatureInformation, out var bestMatch))
353+
{
354+
this.SignatureCompletionContext.BestMatch = bestMatch;
355+
}
356356
}
357357

358358
/// <summary>

0 commit comments

Comments
 (0)