Skip to content

Commit 92e2cbf

Browse files
authored
Merge pull request #8 from SSlinky/dev
Diagnostics Update
2 parents c8265ee + b7dad30 commit 92e2cbf

File tree

11 files changed

+218
-77
lines changed

11 files changed

+218
-77
lines changed

client/src/syntaxes/vba.tmLanguage.yaml

Lines changed: 40 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ repository:
1717
- include: "#methodSignature"
1818
- include: "#continuations" # Consume continuations so they "continue" other matches.
1919
- include: "#enum"
20+
- include: "#struct"
2021
- include: "#syntaxLines" # Split document lines into syntax lines.
2122

2223
continuations:
@@ -40,16 +41,18 @@ repository:
4041

4142
syntaxLines:
4243
name: meta.syntax-lines.vba
43-
match: ((?:[^\n":]|"(?:\\.|[^\n"\\])*")+|"(?:\\.|[^\n"\\])*")
44+
match: ((?:[^\n"':]|"(?:\\.|[^\n"\\])*")+|"(?:\\.|[^\n"\\])*")(?:('.*)*)?
4445
captures:
4546
1: # Split line
4647
patterns:
4748
- include: "#main"
49+
2: # Comments
50+
patterns:
51+
- include: "#comments"
4852

4953
main:
5054
patterns:
5155
- include: "#moduleHeader"
52-
- include: "#struct"
5356
- include: "#declareFunctionSignature"
5457
- include: "#methodSignature"
5558
- include: "#variableDeclarations"
@@ -148,12 +151,11 @@ repository:
148151
repository:
149152
flowDecision:
150153
name: keyword.control.flow.decision.vba
151-
match: '(?i)(^|\s+)(#if|then|#elseif|#else|#end if|select case|case|switch|end select)\b'
152-
# match: '(?i)(^|\s+)([#]?if|then|[#]?elseif|[#]?else|[#]?end if|select case|case|switch|end select)\b'
154+
match: (?i)(^|\s+)(#if|then|#elseif|[#]?else|#end if|select case|case|switch|end select)\b
153155

154156
flowLoop:
155157
name: keyword.control.flow.loop.vba
156-
match: "(?i)\\b(do|exit\\s+do|while|until|loop|for|each|in|to|exit\\s+for|next|with)\\b"
158+
match: (?i)\b(do|exit\s+do|while|until|loop|for|each|in|to|exit\s+for|next|with)\b
157159

158160
forEachLoop:
159161
name: meta.flow.foreach.vba
@@ -170,7 +172,7 @@ repository:
170172

171173
inlineIfElse:
172174
name: meta.flow.inline-if-else.vba
173-
match: (?i)\b(if)\s+(.*?)\s+(then)\s+(.*)\s+(else)\s+(.*)
175+
match: (?i)\s*((?:else)?if)\s+(.*?)\s+(then)\s+(.*)\s+(else)\s+([^'\n]*)
174176
captures:
175177
1:
176178
name: keyword.control.flow.decision.vba
@@ -193,7 +195,7 @@ repository:
193195

194196
inlineIf:
195197
name: meta.flow.inline-if.vba
196-
match: (?i)\b(if)\s+(.*?)\s+(then)
198+
match: (?i)\s*((?:else)?if)\s+(.*?)\s+(then)
197199
captures:
198200
1:
199201
name: keyword.control.flow.decision.vba
@@ -417,13 +419,13 @@ repository:
417419
# The sub-pattern consumes the \n if preceded by line continuation.
418420
# Capturing it there prevents the end pattern being matched.
419421
name: comment.block.vba
420-
begin: (?i)'.*\s_\s*
422+
begin: (?i)\s*'.*\s_\s*
421423
end: \n
422424
patterns:
423425
- include: "#lineContinuation"
424426
apostropheComments:
425-
name: comment.line.apostrophe.vba
426-
match: (?i)'.*
427+
name: comment.line.apostropheXX.vba
428+
match: (?i)\s*'.*
427429
remarkComments:
428430
name: comment.line.remark.vba
429431
match: (?i)(?<=^|:)\s*Rem\b.*
@@ -459,7 +461,7 @@ repository:
459461

460462
enum:
461463
name: meta.enum.declaration.vba
462-
begin: (?i)^\s*((?:(?:Public|Private)\s+)?\s*Enum)\s+([a-z][a-z0-9_]+)(\s+(?:'|Rem).*)
464+
begin: (?i)^\s*((?:(?:Public|Private)\s+)?\s*Enum)\s+([a-z][a-z0-9_]+)(\s+(?:'|Rem).*)?
463465
beginCaptures:
464466
1:
465467
name: storage.type.enum.vba
@@ -471,13 +473,17 @@ repository:
471473
patterns:
472474
- include: "#comment"
473475
- include: "#enumMember"
474-
end: (?i)^\s*End\s+Enum\b
476+
- include: "#language"
477+
end: (?i)^\s*(End\s+Enum)(\s+'.*)?
475478
endCaptures:
476-
0:
479+
1:
477480
name: storage.type.enum.vba
481+
2:
482+
patterns:
483+
- include: "#comments"
478484

479485
enumMember:
480-
match: (?i)^\s*([a-z][a-z0-9_]*)(?:\s+(=)\s+([^\n']*)\s+)?('.*)?$
486+
match: (?i)^\s*([a-z][a-z0-9_]*)(?:\s+(=)\s+([^\n']*))?(\s+(?:'|Rem).*)?
481487
captures:
482488
1:
483489
name: constant.numeric.enum.vba
@@ -493,34 +499,42 @@ repository:
493499

494500
struct:
495501
name: meta.struct.declaration.vba
496-
begin: "(?i)^\\s*((?:(?:Public|Private) )?\\s*Type)\\s+([a-z][a-z0-9_]*)"
502+
begin: (?i)^\s*((?:(?:Public|Private)\s+)?Type)\s+([a-z][a-z0-9_]*)?(\s+(?:'|Rem).*)?
497503
beginCaptures:
498-
1:
504+
1: # Type declaration
499505
name: storage.type.struct.vba
500-
2:
506+
2: # Type name
501507
name: entity.name.type.struct.vba
508+
3: # Comments?
509+
patterns:
510+
- include: "#comments"
502511
patterns:
512+
- include: "#comment"
503513
- include: "#structProperty"
514+
- include: "#language"
504515

505-
end: "(?i)^\\s*End\\s+Type\\b"
516+
end: (?i)^\s*(End\s+Type)(\s+'.*)?
506517
endCaptures:
507-
0:
518+
1:
508519
name: storage.type.struct.vba
520+
2:
521+
patterns:
522+
- include: "#comments"
509523

510524
structProperty:
511-
match: "(?i)^\\s*([a-z][a-z0-9_]*)(\\(.*\\))?(\\s+As\\s+[a-z][a-z0-9_]*)?"
525+
match: (?i)^\s*([a-z][a-z0-9_]*)(\(.*\))?(\s+As\s+[a-z][a-z0-9_]*)?(\s+(?:'|Rem).*)?
512526
captures:
513-
1:
514-
# Property
527+
1: # Property
515528
name: variable.other.readwrite.vba
516-
2:
517-
# Array bounds?
529+
2: # Array bounds?
518530
patterns:
519531
- include: "#language"
520-
3:
521-
# As Type
532+
3: # As Type?
522533
patterns:
523534
- include: "#types"
535+
4: # Comments?
536+
patterns:
537+
- include: "#comments"
524538

525539
declareFunctionSignature:
526540
name: source.declare.signature.vba

package-lock.json

Lines changed: 2 additions & 2 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

package.json

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@
55
"icon": "images/vba-lsp-icon.png",
66
"author": "SSlinky",
77
"license": "MIT",
8-
"version": "1.3.0",
8+
"version": "1.3.2",
99
"repository": {
1010
"type": "git",
1111
"url": "https://github.com/SSlinky/VBA-LanguageServer"

server/src/antlr/vba.g4

Lines changed: 31 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -52,8 +52,7 @@ moduleDeclarationsElement:
5252
comment
5353
| declareStmt
5454
| implementsStmt
55-
| moduleOption
56-
| unknownLine;
55+
| moduleOption;
5756

5857
macroStmt: macroConstStmt | macroIfThenElseStmt;
5958

@@ -461,7 +460,19 @@ stopStmt: STOP;
461460
timeStmt: TIME WS? EQ WS? valueStmt;
462461

463462
typeStmt:
464-
(visibility WS)? TYPE WS ambiguousIdentifier endOfStatement typeStmt_Element* END_TYPE;
463+
(visibility WS)? TYPE WS ambiguousIdentifier endOfStatement (typeStmt_Element|macroTypeIfThenElseStmt)* END_TYPE;
464+
465+
macroTypeIfThenElseStmt:
466+
macroTypeIfBlockStmt macroTypeElseIfBlockStmt* macroTypeElseBlockStmt? MACRO_END_IF endOfStatement;
467+
468+
macroTypeIfBlockStmt:
469+
MACRO_IF WS? ifConditionStmt WS THEN endOfStatement typeStmt_Element*;
470+
471+
macroTypeElseIfBlockStmt:
472+
MACRO_ELSEIF WS? ifConditionStmt WS THEN endOfStatement typeStmt_Element*;
473+
474+
macroTypeElseBlockStmt:
475+
MACRO_ELSE endOfStatement typeStmt_Element*;
465476

466477
typeStmt_Element:
467478
ambiguousIdentifier (WS? LPAREN (WS? subscripts)? WS? RPAREN)? (
@@ -489,28 +500,32 @@ valueStmt:
489500
| implicitCallStmt_InStmt WS? ASSIGN WS? valueStmt # vsAssign
490501
| valueStmt WS? IS WS? valueStmt # vsIs
491502
| valueStmt WS? LIKE WS? valueStmt # vsLike
492-
| valueStmt WS? GEQ WS? valueStmt # vsGeq
493-
| valueStmt WS? LEQ WS? valueStmt # vsLeq
494-
| valueStmt WS? GT WS? valueStmt # vsGt
495-
| valueStmt WS? LT WS? valueStmt # vsLt
496-
| valueStmt WS? NEQ WS? valueStmt # vsNeq
497-
| valueStmt WS? EQ WS? valueStmt # vsEq
498-
| valueStmt WS? POW WS? valueStmt # vsPow
503+
| valueStmt WS? operatorsStmt WS? valueStmt # vsOperator
499504
| MINUS WS? valueStmt # vsNegation
500505
| PLUS WS? valueStmt # vsPlus
501-
| valueStmt WS? DIV WS? valueStmt # vsDiv
502-
| valueStmt WS? MULT WS? valueStmt # vsMult
503506
| valueStmt WS? MOD WS? valueStmt # vsMod
504-
| valueStmt WS? PLUS WS? valueStmt # vsAdd
505-
| valueStmt WS? MINUS WS? valueStmt # vsMinus
506-
| valueStmt WS? AMPERSAND WS? valueStmt # vsAmp
507507
| valueStmt WS? IMP WS? valueStmt # vsImp
508508
| valueStmt WS? EQV WS? valueStmt # vsEqv
509509
| valueStmt WS? XOR WS? valueStmt # vsXor
510510
| valueStmt WS? OR WS? valueStmt # vsOr
511511
| valueStmt WS? AND WS? valueStmt # vsAnd
512512
| NOT WS? valueStmt # vsNot;
513513

514+
operatorsStmt:
515+
(GEQ
516+
| LEQ
517+
| LT
518+
| NEQ
519+
| EQ
520+
| POW
521+
| DIV
522+
| MULT
523+
| MOD
524+
| PLUS
525+
| MINUS
526+
| AMPERSAND
527+
)+;
528+
514529
variableStmt: (DIM | STATIC | visibility) WS (WITHEVENTS WS)? variableListStmt;
515530

516531
variableListStmt:
@@ -1086,7 +1101,7 @@ R_SQUARE_BRACKET: ']';
10861101
STRINGLITERAL: '"' (~["\r\n] | '""')* '"';
10871102
OCTLITERAL: '&O' [0-7]+ '&'?;
10881103
HEXLITERAL: '&H' [0-9A-F]+ '&'?;
1089-
SHORTLITERAL: (PLUS | MINUS)? DIGIT+ ('#' | '&' | '@')?;
1104+
SHORTLITERAL: (PLUS | MINUS)? DIGIT+ ('#' | '&' | '@' | '^')?;
10901105
INTEGERLITERAL: SHORTLITERAL (E SHORTLITERAL)?;
10911106
DOUBLELITERAL: (PLUS | MINUS)? DIGIT* '.' DIGIT+ (E SHORTLITERAL)?;
10921107
DATELITERAL: '#' DATEORTIME '#';
Lines changed: 25 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,30 @@
1-
import { TextDocumentClientCapabilities } from 'vscode-languageserver';
1+
import { CodeDescription, Diagnostic, DiagnosticRelatedInformation, DiagnosticSeverity, DiagnosticTag, Range, TextDocumentClientCapabilities } from 'vscode-languageserver';
22

33

44
function hasDiagnosticRelatedInformationCapability(x: TextDocumentClientCapabilities) {
55
return !!(x && x.publishDiagnostics && x.publishDiagnostics.relatedInformation);
6+
}
7+
8+
abstract class BaseDiagnostic implements Diagnostic {
9+
range: Range;
10+
severity?: DiagnosticSeverity | undefined;
11+
code?: string | number | undefined;
12+
codeDescription?: CodeDescription | undefined;
13+
source?: string | undefined;
14+
abstract message: string;
15+
tags?: DiagnosticTag[] | undefined;
16+
relatedInformation?: DiagnosticRelatedInformation[] | undefined;
17+
data?: unknown;
18+
19+
constructor(range: Range) {
20+
this.range = range;
21+
}
22+
}
23+
24+
25+
export class MultipleOperatorsDiagnostic extends BaseDiagnostic {
26+
message = "Unexpected duplicate operator";
27+
constructor(range: Range) {
28+
super(range);
29+
}
630
}

server/src/project/document.ts

Lines changed: 22 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
1-
import { CancellationToken, Diagnostic, LSPErrorCodes, ResponseError, SemanticTokens, SymbolInformation, SymbolKind } from 'vscode-languageserver';
1+
import { CancellationToken, Diagnostic, LSPErrorCodes, PublishDiagnosticsParams, ResponseError, SemanticTokens, SymbolInformation, SymbolKind } from 'vscode-languageserver';
22
import { Workspace } from './workspace';
33
import { FoldableElement } from './elements/special';
4-
import { BaseSyntaxElement, HasAttribute, HasSemanticToken, HasSymbolInformation } from './elements/base';
4+
import { BaseSyntaxElement, HasAttribute, HasDiagnosticCapability, HasSemanticToken, HasSymbolInformation } from './elements/base';
55
import { Range, TextDocument } from 'vscode-languageserver-textdocument';
66
import { SyntaxParser } from './parser/vbaSyntaxParser';
77
import { FoldingRange } from '../capabilities/folding';
@@ -17,6 +17,7 @@ export abstract class BaseProjectDocument {
1717
protected _unhandledNamedElements: [] = [];
1818
protected _publicScopeDeclarations: Map<string, any> = new Map();
1919
protected _documentScopeDeclarations: Map<string, Map<string, any>> = new Map();
20+
protected _hasDiagnosticElements: HasDiagnosticCapability[] = [];
2021

2122
protected _diagnostics: Diagnostic[] = [];
2223
protected _elementParents: BaseSyntaxElement[] = [];
@@ -77,6 +78,10 @@ export abstract class BaseProjectDocument {
7778
if (await (new SyntaxParser()).parseAsync(this, token)) {
7879
this.isBusy = false;
7980
}
81+
this._hasDiagnosticElements.forEach(element => {
82+
element.evaluateDiagnostics;
83+
this._diagnostics.concat(element.diagnostics);
84+
});
8085
};
8186

8287
registerNamedElementDeclaration(element: any) {
@@ -88,6 +93,11 @@ export abstract class BaseProjectDocument {
8893
throw new Error("Not implemented");
8994
}
9095

96+
registerDiagnosticElement(element: HasDiagnosticCapability) {
97+
console.log("Registering diagnostic element");
98+
this._hasDiagnosticElements.push(element);
99+
}
100+
91101
/**
92102
* Pushes an element to the attribute elements stack.
93103
* Be careful to pair a register action with an appropriate deregister.
@@ -171,6 +181,16 @@ export abstract class BaseProjectDocument {
171181
this.workspace.connection.console.info('Processing request for Folding Range');
172182
return this._foldableElements;
173183
}
184+
185+
getDiagnostics(): PublishDiagnosticsParams {
186+
this._hasDiagnosticElements.forEach(e =>
187+
e.evaluateDiagnostics()
188+
);
189+
return {
190+
uri: this.textDocument.uri,
191+
diagnostics: this._hasDiagnosticElements
192+
.map((e) => e.diagnostics).flat(1) };
193+
}
174194
}
175195

176196

server/src/project/elements/base.ts

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
import { ParserRuleContext } from 'antlr4ts';
2-
import { Range, SemanticTokenModifiers, SemanticTokenTypes, SymbolInformation, SymbolKind } from 'vscode-languageserver';
2+
import { Diagnostic, Range, SemanticTokenModifiers, SemanticTokenTypes, SymbolInformation, SymbolKind } from 'vscode-languageserver';
33
import { Position, TextDocument } from 'vscode-languageserver-textdocument';
44
import { FoldingRangeKind } from '../../capabilities/folding';
55
import { IdentifierElement } from './memory';
@@ -21,6 +21,11 @@ interface SyntaxElement extends ContextOptionalSyntaxElement {
2121
context: ParserRuleContext;
2222
}
2323

24+
export interface HasDiagnosticCapability {
25+
diagnostics: Diagnostic[];
26+
evaluateDiagnostics(): void;
27+
}
28+
2429
export interface HasAttribute {
2530
processAttribute(context: AttributeStmtContext): void;
2631
}
@@ -90,7 +95,7 @@ export abstract class BaseSyntaxElement implements ContextOptionalSyntaxElement
9095
const stopIndex = this.context.stop?.stopIndex ?? startIndex;
9196
return Range.create(
9297
this.document.positionAt(startIndex),
93-
this.document.positionAt(stopIndex)
98+
this.document.positionAt(stopIndex + 1)
9499
);
95100
}
96101
}

0 commit comments

Comments
 (0)