Skip to content

Commit fdb2658

Browse files
authored
Merge pull request #2782 from TypeCobolTeam/v2.9.3
v2.9.3
2 parents 6b9f6b0 + 302527a commit fdb2658

File tree

6 files changed

+239
-66
lines changed

6 files changed

+239
-66
lines changed

TypeCobol.LanguageServer.Test/RefactoringTest.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -126,7 +126,7 @@ private static void TestDirectory([CallerMemberName] string directoryName = null
126126
path = Path.Combine(path, directoryName);
127127

128128
var failedTests = new List<(string TestFile, Exception Exception)>();
129-
foreach (var testFile in Directory.GetFiles(path, "*.*", SearchOption.AllDirectories))
129+
foreach (var testFile in Directory.GetFiles(path, "*.cbl", SearchOption.AllDirectories))
130130
{
131131
try
132132
{
Lines changed: 133 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,133 @@
1+
IDENTIFICATION DIVISION.
2+
PROGRAM-ID. TCOMFL06.
3+
DATA DIVISION.
4+
WORKING-STORAGE SECTION.
5+
01 one-level.
6+
05 root-table-1 OCCURS 10.
7+
10 var1 PIC X.
8+
10 var2 PIC X.
9+
01 two-levels.
10+
05 root-table-2 OCCURS 100.
11+
10 table-level1-1 OCCURS 20.
12+
15 var3 PIC X.
13+
15 var4 PIC X.
14+
COPY ThreeLevels.
15+
PROCEDURE DIVISION.
16+
GOBACK
17+
.
18+
END PROGRAM TCOMFL06.
19+
-------------------------------------------------------------------------------------------------
20+
TypeCobol.LanguageServer.Commands.InsertVariableDisplay.InsertVariableDisplayRefactoringProcessor
21+
-------------------------------------------------------------------------------------------------
22+
[
23+
{
24+
"textDocument": { "uri": "file:/test.expected.cbl" },
25+
"position": { "line": 14, "character": 26 }
26+
},
27+
false,
28+
{
29+
"vm": 1, "idx": 0, "ch": [
30+
{
31+
"vm": 2, "name": "one-level"
32+
},
33+
{
34+
"vm": 2, "name": "two-levels"
35+
},
36+
{
37+
"vm": 2, "name": "three-levels"
38+
}
39+
]
40+
}
41+
]
42+
-------------------------------------------------------------------------------------------------
43+
refactoring.label=Debug instructions successfully generated.
44+
refactoring.source=
45+
IDENTIFICATION DIVISION.
46+
PROGRAM-ID. TCOMFL06.
47+
DATA DIVISION.
48+
WORKING-STORAGE SECTION.
49+
01 one-level.
50+
05 root-table-1 OCCURS 10.
51+
10 var1 PIC X.
52+
10 var2 PIC X.
53+
01 two-levels.
54+
05 root-table-2 OCCURS 100.
55+
10 table-level1-1 OCCURS 20.
56+
15 var3 PIC X.
57+
15 var4 PIC X.
58+
COPY ThreeLevels.
59+
*<DBG>InsertVariableDisplay 1959/09/18 11:09 TESTUSER
60+
D77 Idx-d4df4249-1 PIC 9(4) COMP-5.
61+
D77 Idx-d4df4249-2 PIC 9(4) COMP-5.
62+
D77 Idx-d4df4249-3 PIC 9(4) COMP-5.
63+
*</DBG>
64+
65+
PROCEDURE DIVISION.
66+
*<DBG>InsertVariableDisplay 1959/09/18 11:09 TESTUSER
67+
D DISPLAY 'one-level'
68+
D PERFORM VARYING Idx-d4df4249-1 FROM 1 BY 1 UNTIL
69+
D Idx-d4df4249-1 > 10
70+
D DISPLAY ' root-table-1 (' Idx-d4df4249-1 ')'
71+
D DISPLAY ' var1 (' Idx-d4df4249-1 ') <' var1
72+
D (Idx-d4df4249-1) '>'
73+
D DISPLAY ' var2 (' Idx-d4df4249-1 ') <' var2
74+
D (Idx-d4df4249-1) '>'
75+
D DISPLAY ' ---------------------------------------------'
76+
D '-------------------------------------------------'
77+
D '----------------------'
78+
D END-PERFORM
79+
D DISPLAY 'two-levels'
80+
D PERFORM VARYING Idx-d4df4249-1 FROM 1 BY 1 UNTIL
81+
D Idx-d4df4249-1 > 100
82+
D DISPLAY ' root-table-2 (' Idx-d4df4249-1 ')'
83+
D PERFORM VARYING Idx-d4df4249-2 FROM 1 BY 1 UNTIL
84+
D Idx-d4df4249-2 > 20
85+
D DISPLAY ' table-level1-1 (' Idx-d4df4249-1 ' '
86+
D Idx-d4df4249-2 ')'
87+
D DISPLAY ' var3 (' Idx-d4df4249-1 ' ' Idx-d4df4249-2
88+
D ') <' var3 (Idx-d4df4249-1 Idx-d4df4249-2) '>'
89+
D DISPLAY ' var4 (' Idx-d4df4249-1 ' ' Idx-d4df4249-2
90+
D ') <' var4 (Idx-d4df4249-1 Idx-d4df4249-2) '>'
91+
D DISPLAY ' -----------------------------------------'
92+
D '-----------------------------------------------'
93+
D '--------------------------'
94+
D END-PERFORM
95+
D DISPLAY ' ---------------------------------------------'
96+
D '-------------------------------------------------'
97+
D '----------------------'
98+
D END-PERFORM
99+
D DISPLAY 'three-levels'
100+
D PERFORM VARYING Idx-d4df4249-1 FROM 1 BY 1 UNTIL
101+
D Idx-d4df4249-1 > 1000
102+
D DISPLAY ' root-table-3 (' Idx-d4df4249-1 ')'
103+
D PERFORM VARYING Idx-d4df4249-2 FROM 1 BY 1 UNTIL
104+
D Idx-d4df4249-2 > 200
105+
D DISPLAY ' table-level1-2 (' Idx-d4df4249-1 ' '
106+
D Idx-d4df4249-2 ')'
107+
D PERFORM VARYING Idx-d4df4249-3 FROM 1 BY 1 UNTIL
108+
D Idx-d4df4249-3 > 30
109+
D DISPLAY ' table-level2-1 (' Idx-d4df4249-1 ' '
110+
D Idx-d4df4249-2 ' ' Idx-d4df4249-3 ')'
111+
D DISPLAY ' var5 (' Idx-d4df4249-1 ' '
112+
D Idx-d4df4249-2 ' ' Idx-d4df4249-3 ') <' var5
113+
D (Idx-d4df4249-1 Idx-d4df4249-2 Idx-d4df4249-3) '>'
114+
D DISPLAY ' var6 (' Idx-d4df4249-1 ' '
115+
D Idx-d4df4249-2 ' ' Idx-d4df4249-3 ') <' var6
116+
D (Idx-d4df4249-1 Idx-d4df4249-2 Idx-d4df4249-3) '>'
117+
D DISPLAY ' -------------------------------------'
118+
D '---------------------------------------------'
119+
D '------------------------------'
120+
D END-PERFORM
121+
D DISPLAY ' -----------------------------------------'
122+
D '-----------------------------------------------'
123+
D '--------------------------'
124+
D END-PERFORM
125+
D DISPLAY ' ---------------------------------------------'
126+
D '-------------------------------------------------'
127+
D '----------------------'
128+
D END-PERFORM
129+
*</DBG>
130+
131+
GOBACK
132+
.
133+
END PROGRAM TCOMFL06.
Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
01 three-levels.
2+
05 root-table-3 OCCURS 1000.
3+
10 table-level1-2 OCCURS 200.
4+
15 table-level2-1 OCCURS 30.
5+
20 var5 PIC X.
6+
20 var6 PIC X.

TypeCobol.LanguageServer.Test/RefactoringTests/RefactoringProcessorTest.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -64,7 +64,7 @@ public static RefactoringProcessorTest LoadFrom(string testDataFilePath)
6464
var options = new TypeCobolOptions();
6565
var format = DocumentFormat.RDZReferenceFormat;
6666
bool isCopy = !testData.OriginalSource.TrimStart().StartsWith("IDENTIFICATION", StringComparison.OrdinalIgnoreCase); // Simple but should be enough, does not support copys starting with IDENTIFICATION...
67-
var target = ParserUtils.ParseCobolString(testData.OriginalSource, isCopy, options, format);
67+
var target = ParserUtils.ParseCobolString(testData.OriginalSource, isCopy, options, format, Path.GetDirectoryName(testDataFilePath)); // Add directory containing the test itself as a copy library in order to find included COPYs
6868

6969
// Identify processor to test
7070
var refactoringProcessor = _RefactoringProcessors[testData.ProcessorType];

TypeCobol.LanguageServer/Commands/InsertVariableDisplay/InsertVariableDisplayRefactoringProcessor.cs

Lines changed: 93 additions & 63 deletions
Original file line numberDiff line numberDiff line change
@@ -157,90 +157,120 @@ private static GeneratedRoot GenerateDisplayStatements(DataSection dataSection,
157157
}
158158

159159
private static TextEdit InsertBefore(ISearchableReadOnlyList<ICodeElementsLine> codeLines, Node node, string code)
160+
=> InsertBefore(codeLines, GetFirstToken(node), code);
161+
162+
private static TextEdit InsertAfter(ISearchableReadOnlyList<ICodeElementsLine> codeLines, Node node, string code)
163+
=> InsertAfter(codeLines, GetLastToken(node), code);
164+
165+
private static Token GetFirstToken(Node node)
166+
{
167+
Debug.Assert(node != null);
168+
Debug.Assert(node.CodeElement != null);
169+
170+
if (node.CodeElement.IsInsideCopy())
171+
{
172+
// Go back up to including COPY directive and return its first token (the COPY token)
173+
return node.CodeElement.FirstCopyDirective.COPYToken;
174+
}
175+
176+
// First token of CodeElement
177+
Debug.Assert(node.CodeElement.ConsumedTokens.Count > 0);
178+
return node.CodeElement.ConsumedTokens[0];
179+
}
180+
181+
private static Token GetLastToken(Node node)
160182
{
183+
// Do not insert inside statements having a body (statement with nested statements)
184+
// -> Reposition at the end of the whole statement (i.e. on its matching END-xxx node).
185+
if (node is StatementWithBody) node = node.GetLastNode();
186+
187+
Debug.Assert(node != null);
161188
Debug.Assert(node.CodeElement != null);
162-
int line = node.CodeElement.Line; // On same line and inserted text ends with a line break
189+
190+
if (node.CodeElement.IsInsideCopy())
191+
{
192+
// Go back up to including COPY directive and return its last token
193+
var copyDirectiveTokens = node.CodeElement.FirstCopyDirective.ConsumedTokens.SelectedTokensOnSeveralLines;
194+
Debug.Assert(copyDirectiveTokens.Length > 0);
195+
Debug.Assert(copyDirectiveTokens[^1].Count > 0);
196+
return copyDirectiveTokens[^1][^1];
197+
}
198+
199+
// Last token of CodeElement
200+
Debug.Assert(node.CodeElement.ConsumedTokens.Count > 0);
201+
return node.CodeElement.ConsumedTokens[^1];
202+
}
203+
204+
private static TextEdit InsertBefore(ISearchableReadOnlyList<ICodeElementsLine> codeLines, Token token, string code)
205+
{
206+
int line = token.Line; // On same line and inserted text ends with a line break
163207
string newText = code + Environment.NewLine;
164208
int character = 0; // At beginning of the line, except when CodeElement is not the first
165209

166-
var insertionToken = node.CodeElement.ConsumedTokens.FirstOrDefault();
167-
if (insertionToken != null)
210+
// Is the first token of the CodeElement also the first token on the line ?
211+
var tokensLine = token.TokensLine;
212+
if (token != tokensLine.SourceTokens.First())
168213
{
169-
// Is the first token of the CodeElement also the first token on the line ?
170-
var tokensLine = insertionToken.TokensLine;
171-
if (insertionToken != tokensLine.SourceTokens.First())
172-
{
173-
// Insertion point is right before CodeElement
174-
character = node.CodeElement.StartIndex;
175-
// Start a new line and align text located beyond insertion point on its current column
176-
newText = $"{Environment.NewLine}{newText}{BeginLine(tokensLine.IndicatorChar, character)}";
177-
}
178-
else
214+
// Insertion point is right before CodeElement
215+
character = token.StartIndex;
216+
// Start a new line and align text located beyond insertion point on its current column
217+
newText = $"{Environment.NewLine}{newText}{BeginLine(tokensLine.IndicatorChar, character)}";
218+
}
219+
else
220+
{
221+
// Nothing before insertion point, check for comments preceding the insertion line
222+
int lineIndex = line - 2; // Start with the index of the line before insertion line (line is 1-based whereas lineIndex is 0-based)
223+
while (lineIndex >= 0)
179224
{
180-
// Nothing before insertion point, check for comments preceding the insertion line
181-
int lineIndex = line - 2; // Start with the index of the line before insertion line (line is 1-based whereas lineIndex is 0-based)
182-
while (lineIndex >= 0)
225+
var codeLine = codeLines[lineIndex];
226+
if (IsComment(codeLine) || codeLine.Type == CobolTextLineType.MultiFormalizedComment)
183227
{
184-
var codeLine = codeLines[lineIndex];
185-
if (IsComment(codeLine) || codeLine.Type == CobolTextLineType.MultiFormalizedComment)
186-
{
187-
// Insert before this comment/debug line
188-
line = lineIndex + 1;
189-
character = 0;
190-
lineIndex--;
191-
}
192-
else
193-
{
194-
// Source line: keep current insertion position
195-
break;
196-
}
228+
// Insert before this comment/debug line
229+
line = lineIndex + 1;
230+
character = 0;
231+
lineIndex--;
232+
}
233+
else
234+
{
235+
// Source line: keep current insertion position
236+
break;
197237
}
198238
}
199239
}
200240

201241
return TextEdit.Insert(new Position() { line = line, character = character }, newText);
202242
}
203243

204-
private static TextEdit InsertAfter(ISearchableReadOnlyList<ICodeElementsLine> codeLines, Node node, string code)
244+
private static TextEdit InsertAfter(ISearchableReadOnlyList<ICodeElementsLine> codeLines, Token token, string code)
205245
{
206-
// Do not insert inside statements having a body (statement with nested statements)
207-
// -> Reposition at the end of the whole statement (on its matching END-xxx node).
208-
if (node is StatementWithBody) node = node.GetLastNode();
209-
210-
Debug.Assert(node != null);
211-
Debug.Assert(node.CodeElement != null);
212-
int line = node.CodeElement.LineEnd; // On same line and inserted text starts with a line break:
246+
int line = token.Line; // On same line and inserted text starts with a line break:
213247
string newText = Environment.NewLine + code;
214-
int character = node.CodeElement.StopIndex + 1; // At CodeElement end
248+
int character = token.StopIndex + 1; // At CodeElement/CopyDirective end
215249

216-
var insertionToken = node.CodeElement.ConsumedTokens.LastOrDefault();
217-
if (insertionToken != null)
250+
// Is there anything after insertion point ?
251+
var tokensLine = token.TokensLine;
252+
if (tokensLine.Length > character)
218253
{
219-
// Is there anything after insertion point ?
220-
var tokensLine = insertionToken.TokensLine;
221-
if (tokensLine.Length > character)
222-
{
223-
// Align text located beyond insertion point on its current column
224-
newText += BeginLine(tokensLine.IndicatorChar, character);
225-
}
226-
else
254+
// Align text located beyond insertion point on its current column
255+
newText += BeginLine(tokensLine.IndicatorChar, character);
256+
}
257+
else
258+
{
259+
// Nothing after insertion point, check for comments following the insertion line
260+
int lineIndex = line; // Initialize with insertion line which is 1-based, thus we start here with the index of the line after insertion line
261+
while (lineIndex < codeLines.Count)
227262
{
228-
// Nothing after insertion point, check for comments following the insertion line
229-
int lineIndex = line; // Initialize with insertion line which is 1-based, thus we start here with the index of the line after insertion line
230-
while (lineIndex < codeLines.Count)
263+
var codeLine = codeLines[lineIndex];
264+
if (IsComment(codeLine)) // Do not consider MultiFormalizedComment as they are attached to the code following them
265+
{
266+
// Insert after this comment/debug line
267+
line = ++lineIndex;
268+
character = codeLine.Length;
269+
}
270+
else
231271
{
232-
var codeLine = codeLines[lineIndex];
233-
if (IsComment(codeLine)) // Do not consider MultiFormalizedComment as they are attached to the code following them
234-
{
235-
// Insert after this comment/debug line
236-
line = ++lineIndex;
237-
character = codeLine.Length;
238-
}
239-
else
240-
{
241-
// Source line: keep current insertion position
242-
break;
243-
}
272+
// Source line: keep current insertion position
273+
break;
244274
}
245275
}
246276
}

TypeCobol.Test/Utils/ParserUtils.cs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -53,13 +53,17 @@ public static CompilationUnit ParseCobolFile(string textName, string folder, boo
5353
return compiler.CompilationResultsForProgram;
5454
}
5555

56-
public static CompilationUnit ParseCobolString(string cobolString, bool asPartOfACopy, TypeCobolOptions options, DocumentFormat enclosingDocumentFormat)
56+
public static CompilationUnit ParseCobolString(string cobolString, bool asPartOfACopy, TypeCobolOptions options, DocumentFormat enclosingDocumentFormat, params string[] copyLibraries)
5757
{
5858
// Load string into new document
5959
var textDocument = new ReadOnlyTextDocument("In-memory document", options.GetEncodingForAlphanumericLiterals(), enclosingDocumentFormat.ColumnsLayout, asPartOfACopy, string.Empty);
6060
textDocument.LoadChars(cobolString);
6161

6262
var project = new CompilationProject("Empty project", ".", new[] { ".cbl", ".cpy" }, enclosingDocumentFormat, options, null);
63+
foreach (var copyLibrary in copyLibraries)
64+
{
65+
project.SourceFileProvider.AddLocalDirectoryLibrary(copyLibrary, false, [".cpy"], enclosingDocumentFormat.Encoding, enclosingDocumentFormat.EndOfLineDelimiter, enclosingDocumentFormat.FixedLineLength);
66+
}
6367

6468
var compiler = new FileCompiler(textDocument, project.SourceFileProvider, project, options, project);
6569
compiler.CompileOnce();

0 commit comments

Comments
 (0)