Skip to content

Commit 1780667

Browse files
committed
Send it
1 parent 8cef26e commit 1780667

File tree

4 files changed

+133
-67
lines changed

4 files changed

+133
-67
lines changed

client/src/syntaxes/vba.tmLanguage.yaml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -582,6 +582,7 @@ repository:
582582
arg:
583583
patterns:
584584
- include: "#kwarg"
585+
- include: "#literals"
585586
- include: "#lineConcat"
586587
- include: "#language"
587588

server/src/docInfo.ts

Lines changed: 91 additions & 51 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,14 @@
1-
import { CompletionItem, Diagnostic, DiagnosticRelatedInformation, DiagnosticSeverity, DidChangeConfigurationParams, DidChangeWatchedFilesParams, DocumentSymbol, FoldingRange, Hover, HoverParams, Location, NotificationHandler, Position, PublishDiagnosticsParams, Range, SemanticTokenModifiers, SemanticTokens, SemanticTokensParams, SemanticTokensRangeParams, SemanticTokensRequest, SymbolInformation, SymbolKind, TextDocumentPositionParams, TextDocuments, uinteger, _Connection } from 'vscode-languageserver';
21
import { TextDocument } from 'vscode-languageserver-textdocument';
3-
import { LiteralContext } from './antlr/out/vbaParser';
4-
import { SemanticToken, sortSemanticTokens } from './capabilities/vbaSemanticTokens';
5-
import { sleep, rangeIsChildOfElement } from './utils/helpers';
6-
import { IdentifiableSyntaxElement, IdentifierElement, MethodElement, ModuleAttribute, ModuleElement, SyntaxElement, VariableDeclarationElement, VariableStatementElement } from './utils/vbaSyntaxElements';
7-
import { ResultsContainer, SyntaxParser } from './utils/vbaSyntaxParser';
82

3+
import { MethodElement } from './parser/elements/method';
4+
import { ModuleElement } from './parser/elements/module';
5+
import { sortSemanticTokens } from './capabilities/vbaSemanticTokens';
6+
import { sleep, rangeIsChildOfElement } from './utils/helpers';
7+
import { FoldableElement, SyntaxElement } from './parser/elements/base';
8+
import { ResultsContainer, SyntaxParser } from './parser/vbaSyntaxParser';
9+
import { VariableAssignElement, VariableDeclarationElement, VariableStatementElement } from './parser/elements/variable';
10+
11+
import { CompletionItem, Diagnostic, DiagnosticRelatedInformation, DiagnosticSeverity, DidChangeConfigurationParams, DidChangeWatchedFilesParams, DocumentSymbol, FoldingRange, Hover, HoverParams, Location, NotificationHandler, Position, PublishDiagnosticsParams, Range, SemanticTokenModifiers, SemanticTokens, SemanticTokensParams, SemanticTokensRangeParams, SemanticTokensRequest, SymbolInformation, SymbolKind, TextDocumentPositionParams, TextDocuments, uinteger, _Connection } from 'vscode-languageserver';
912

1013
declare global {
1114
interface Map<K, V> {
@@ -150,16 +153,18 @@ export class DocumentInformation implements ResultsContainer {
150153
module?: ModuleElement;
151154
elements: SyntaxElement[] = [];
152155
attrubutes: Map<string, string> = new Map();
156+
foldingRanges: FoldingRange[] = [];
153157
isBusy = true;
154-
scope: Scope;
155-
158+
156159
private docUri: string;
157160
private ancestors: SyntaxElement[] = [];
161+
private documentScope: Scope;
158162

159163
constructor(scope: Scope, docUri: string) {
164+
this.docUri = docUri;
160165
scope.links.set(docUri, new Map());
161-
this.scope = scope;
162166
this.docUri = docUri;
167+
this.documentScope = scope;
163168
}
164169

165170
addModule(emt: ModuleElement) {
@@ -168,6 +173,10 @@ export class DocumentInformation implements ResultsContainer {
168173
this.ancestors.push(emt);
169174
}
170175

176+
addFoldingRange(emt: FoldableElement) {
177+
this.foldingRanges.push(emt.foldingRange()!);
178+
}
179+
171180
addElement(emt: SyntaxElement) {
172181
// Find the parent element.
173182
while (this.ancestors) {
@@ -177,7 +186,6 @@ export class DocumentInformation implements ResultsContainer {
177186
pnt.children.push(emt);
178187
this.ancestors.push(pnt);
179188
this.ancestors.push(emt);
180-
emt.fqName = pnt.fqName;
181189
break;
182190
}
183191
}
@@ -189,23 +197,11 @@ export class DocumentInformation implements ResultsContainer {
189197
// Also add identifier elements
190198
if (emt.identifier) {
191199
this.addElement(emt.identifier);
192-
emt.fqName = `${(emt.fqName ?? '')}.${emt.identifier.text}`;
200+
// emt.fqName = `${(emt.fqName ?? '')}.${emt.identifier.text}`;
193201
}
194-
}
195202

196-
// addName(ident: IdentifierElement, emt: MethodElement | VariableStatementElement) {
197-
// const scope = this.documentScope.links.get(this.docUri)!;
198-
// const hoverText = emt.getHoverText();
199-
// if (scope.has(ident.text)) {
200-
// const scopeEls = scope.get(ident.text)!;
201-
// scopeEls[0] = emt;
202-
// scopeEls.filter((x): x is SyntaxElement => !!(x))
203-
// .forEach((x) => x.hoverText = hoverText);
204-
// return;
205-
// }
206-
// scope.set(ident.text, [emt]);
207-
// emt.hoverText = hoverText;
208-
// }
203+
return this;
204+
}
209205

210206
/**
211207
* Use this method to set as the current scope.
@@ -221,9 +217,8 @@ export class DocumentInformation implements ResultsContainer {
221217

222218
addScopedDeclaration(emt: MethodElement | VariableDeclarationElement) {
223219
// Add a declared scope.
224-
// this.addElement(emt);
225220
const elId = emt.identifier!.text;
226-
const link = this.getNameLink(elId, emt.parent?.fqName ?? '', emt.hasPrivateModifier);
221+
const link = this.getNameLink(elId, emt.parent?.namespace ?? '', emt.hasPrivateModifier);
227222
link.declarations.push(emt);
228223

229224
// Check the undeclared links and merge if found.
@@ -233,14 +228,20 @@ export class DocumentInformation implements ResultsContainer {
233228
link.merge(undeclaredLink);
234229
undeclaredScope.delete(elId);
235230
}
236-
237-
this.addElement(emt);
238231
}
239232

240-
addScopedReference(emt: IdentifierElement) {
241-
const link = this.getNameLink(emt.identifier!.text, emt.parent?.fqName ?? '', false, true);
242-
link.references.push(emt);
243-
this.addElement(emt);
233+
// addScopeReference(emt: VariableAssignElement) {
234+
// const link = this.getNameLink(emt.identifier!.text, emt.parent?.namespace ?? '', false, true);
235+
// link.references.push(emt);
236+
// }
237+
238+
/**
239+
* Creates scope references for the left and right sides
240+
* of the variable assignment if they exist.
241+
* @param emt the variable assignment element.
242+
*/
243+
addScopeReferences(emt: VariableAssignElement) {
244+
throw new Error("Not implemented exception");
244245
}
245246

246247
private getNameLink(identifier: string, fqName: string, isPrivate = false, searchScopes = false): NameLink {
@@ -261,7 +262,7 @@ export class DocumentInformation implements ResultsContainer {
261262
const globalScope = this.scope.getScope('global');
262263
const localScope = this.scope.getScope(this.docUri);
263264

264-
const isAtModuleLevel = (fqName ?? '') === this.docUri;
265+
const isAtModuleLevel = !(fqName ?? '').includes('.');
265266
return (isAtModuleLevel && !isPrivate) ? globalScope : localScope;
266267
}
267268

@@ -278,17 +279,18 @@ export class DocumentInformation implements ResultsContainer {
278279

279280

280281
finalise() {
281-
this.scope.processLinks(this.docUri, true);
282+
// TODO: Intelligently pass opt. explicit.
283+
this.documentScope.processLinks(this.docUri, true);
282284
this.isBusy = false;
283285
}
284286

285-
setModuleAttribute = (attr: ModuleAttribute) =>
286-
this.attrubutes.set(attr.key(), attr.value());
287+
// setModuleAttribute = (attr: ModuleAttribute) =>
288+
// this.attrubutes.set(attr.key(), attr.value());
287289

288-
setModuleIdentifier(ctx: LiteralContext, doc: TextDocument) {
289-
if (this.module)
290-
this.module.identifier = new IdentifierElement(ctx, doc);
291-
}
290+
// setModuleIdentifier(ctx: LiteralContext, doc: TextDocument) {
291+
// if (this.module)
292+
// this.module.identifier = new IdentifierElement(ctx, doc);
293+
// }
292294

293295
getHover = (p: Position) =>
294296
this.getElementAtPosition(p)?.hover();
@@ -323,14 +325,15 @@ export class DocumentInformation implements ResultsContainer {
323325
// Filter eligible parents by range.
324326
let parents = this.elements.filter((x) => rangeIsChildOfElement(r, x));
325327
if (parents.length === 0) { return; }
326-
if (parents.length === 1) { return parents[0]; }
328+
if (parents.length === 1) { console.log(`hover@${r.toString()}: ${parents[0].identifier?.text}`); return parents[0]; }
327329

328330
// Narrow parents down to the one(s) with the narrowest row scope.
329331
// In the incredibly unlikely case that we have two parents with the same number of rows
330332
// and they span more than one row, then it's all too hard. Just pick one.
331333
const minRows = Math.min(...parents.map((x) => x.range.end.line - x.range.start.line));
332334
parents = parents.filter((x) => x.range.end.line - x.range.start.line === minRows);
333335
if (parents.length === 1 || minRows > 0) {
336+
console.log(`hover@${this.rangeAddress(r)}: ${parents[0].toString()}`);
334337
return parents[0];
335338
}
336339

@@ -358,7 +361,7 @@ export class DocumentInformation implements ResultsContainer {
358361
}
359362

360363
getDiagnostics(): PublishDiagnosticsParams {
361-
return {uri: this.docUri, diagnostics: this.elements.map((e) => e.diagnostics).flat(1)};
364+
return { uri: this.docUri, diagnostics: this.elements.map((e) => e.diagnostics).flat(1) };
362365
}
363366

364367
getSymbols = (uri: string): SymbolInformation[] =>
@@ -367,11 +370,26 @@ export class DocumentInformation implements ResultsContainer {
367370
.map((x) => x.symbolInformation(uri))
368371
.filter((x): x is SymbolInformation => !!x);
369372

373+
// getFoldingRanges = (): (FoldingRange)[] =>
374+
// this.elements
375+
// .filter((x) => !(x instanceof ModuleElement))
376+
// .map((x) => x.foldingRange())
377+
// .filter((x): x is FoldingRange => !!x);
378+
370379
getFoldingRanges = (): (FoldingRange)[] =>
371-
this.elements
372-
.filter((x) => !(x instanceof ModuleElement))
373-
.map((x) => x.foldingRange())
374-
.filter((x): x is FoldingRange => !!x);
380+
this.foldingRanges;
381+
382+
private rangeAddress(r: Range): string {
383+
const sl = r.start.line;
384+
const el = r.end.line;
385+
const sc = r.start.character;
386+
const ec = r.end.character;
387+
388+
if(sl==el) {
389+
return `${sl}:${sc}-${ec}`;
390+
}
391+
return `${sl}:${sc}-${el}:${ec}`;
392+
}
375393
}
376394

377395
class Scope {
@@ -384,6 +402,11 @@ class Scope {
384402
this.links.set('global', new Map());
385403
}
386404

405+
/**
406+
* Gets the scope related to the key. Lazy instantiates.
407+
* @param key the key of the scope to get.
408+
* @returns a Scope.
409+
*/
387410
getScope(key: string): Map<string, NameLink> {
388411
if (key !== this.currentDoc) {
389412
this.currentDoc = key;
@@ -405,10 +428,11 @@ class Scope {
405428

406429
processLinks(key: string, optExplicit = false) {
407430
// TODO: check global for undeclareds
431+
// TODO: implement explicit paths, e.g. Module1.MyVar
408432
const undeclared = this.getScope(`undeclared|${key}`);
409-
const docScopes = this.getScope(key);
410-
undeclared.forEach((v, k) => docScopes.set(k, v));
411-
docScopes.forEach((x) => x.process(optExplicit));
433+
const docScope = this.getScope(key);
434+
undeclared.forEach((v, k) => docScope.set(k, v));
435+
docScope.forEach((x) => x.process(optExplicit));
412436
}
413437
}
414438

@@ -419,6 +443,7 @@ class NameLink {
419443
// 0: Variable or method not declared.
420444
// 1: Declared once.
421445
// 2: Multiple conflicting declarations.
446+
private _declarations: SyntaxElement[] = [];
422447
declarations: SyntaxElement[] = [];
423448

424449
// The places this name is referenced.
@@ -438,6 +463,7 @@ class NameLink {
438463
}
439464

440465
process(optExplicit = false) {
466+
this.addDeclarationReferences();
441467
this.processDiagnosticRelatedInformation();
442468
this.validateDeclarationCount(optExplicit);
443469
this.validateMethodSignatures();
@@ -446,6 +472,20 @@ class NameLink {
446472
this.assignDiagnostics();
447473
}
448474

475+
private addDeclarationReferences() {
476+
this.references.forEach((x) => this.addDecToRef(x));
477+
}
478+
479+
private addDecToRef(ref: SyntaxElement) {
480+
if(!(ref instanceof VariableStatementElement)) {
481+
return;
482+
}
483+
const dec = this.declarations[0];
484+
if(dec instanceof MethodElement) {
485+
ref.setDeclaredType(dec);
486+
}
487+
}
488+
449489
private processDiagnosticRelatedInformation() {
450490
this.diagnosticRelatedInfo = this.declarations
451491
.concat(this.references)
@@ -490,7 +530,7 @@ class NameLink {
490530
return;
491531
}
492532

493-
this.references.forEach((x) => x.semanticToken =
533+
this.references.forEach((x) => x.semanticToken =
494534
this.declarations[0]
495535
.semanticToken
496536
?.toNewRange(x.range));

server/src/server.ts

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,6 @@ import {
99
DidChangeConfigurationNotification,
1010
TextDocumentSyncKind,
1111
InitializeResult,
12-
Hover,
1312
SemanticTokensParams,
1413
} from 'vscode-languageserver/node';
1514

@@ -91,14 +90,6 @@ connection.onInitialized(() => {
9190
}
9291
});
9392

94-
95-
// connection.onHover(({textDocument, position}): Hover => {
96-
// // Can make this into a proper hover provider later.
97-
// return {
98-
// contents: "Hello, HOVER world!"
99-
// };
100-
// });
101-
10293
// The example settings
10394
interface ExampleSettings {
10495
maxNumberOfProblems: number;

0 commit comments

Comments
 (0)