Skip to content

Commit 6c60ee4

Browse files
committed
Switched to proper AST evaluation rather than transpile to TS
1 parent 952991c commit 6c60ee4

File tree

3 files changed

+250
-24
lines changed

3 files changed

+250
-24
lines changed

server/src/antlr/vbapre.g4

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,8 @@ orderOfOps2: MOD;
6060
orderOfOps3: PLUS | SUBT;
6161
orderOfOps4: AMP;
6262
orderOfOps5: LIKE | (LT | GT)? (LT | GT | EQ) | EQ;
63-
orderOfOps6: AND | OR | XOR | EQV | IMP;
63+
orderOfOps6: anyWord;
64+
// orderOfOps6: AND | OR | XOR | EQV | IMP;
6465

6566

6667
directiveExpression
@@ -153,7 +154,6 @@ reservedWord
153154
| PLUS
154155
| SUBT
155156
| THEN
156-
| compilerConstant
157157
;
158158

159159
unreservedWord
@@ -166,6 +166,7 @@ unreservedWord
166166
| NOTHING
167167
| NULL_
168168
| TRUE
169+
| compilerConstant
169170
;
170171

171172
anyWord: ( unreservedWord | reservedWord)+;

server/src/capabilities/diagnostics.ts

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -96,6 +96,14 @@ export class AmbiguousNameDiagnostic extends BaseDiagnostic {
9696
}
9797
}
9898

99+
// test
100+
export class CannotEvaluateExpressionDiagnostic extends BaseDiagnostic {
101+
severity = DiagnosticSeverity.Error;
102+
constructor(range: Range, message: string) {
103+
super(range);
104+
this.message = `Cannot evaluate expression: '${message}'.`;
105+
}
106+
}
99107

100108
// test
101109
export class ShadowDeclarationDiagnostic extends BaseDiagnostic {

server/src/project/elements/precompiled.ts

Lines changed: 239 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -2,39 +2,58 @@
22
import { TextDocument } from 'vscode-languageserver-textdocument';
33

44
// Antlr
5-
import { CompilerConditionalBlockContext, CompilerDefaultBlockContext, CompilerIfBlockContext, ConstDirectiveStatementContext } from '../../antlr/out/vbapreParser';
5+
import { CompilerConditionalBlockContext, CompilerDefaultBlockContext, CompilerIfBlockContext, ConstDirectiveStatementContext, DirectiveExpressionContext, DirectiveLiteralExpressionContext, OrderOfOps1Context, OrderOfOps2Context, OrderOfOps3Context, OrderOfOps4Context, OrderOfOps5Context, OrderOfOps6Context } from '../../antlr/out/vbapreParser';
66

77
// Project
88
import { DiagnosticCapability, FoldingRangeCapability, IdentifierCapability } from '../../capabilities/capabilities';
99
import { BaseRuleSyntaxElement } from '../elements/base';
10-
import { UnreachableCodeDiagnostic } from '../../capabilities/diagnostics';
10+
import { CannotEvaluateExpressionDiagnostic, UnreachableCodeDiagnostic } from '../../capabilities/diagnostics';
11+
import { Services } from '../../injection/services';
1112

1213

1314
type DocumentSettings = { environment: { os: string, version: string } };
1415

1516
export class CompilerDirectiveElement extends BaseRuleSyntaxElement<ConstDirectiveStatementContext> {
1617
identifierCapability: IdentifierCapability;
18+
diagnosticCapability: DiagnosticCapability;
1719

18-
constructor(ctx: ConstDirectiveStatementContext,
20+
constructor(
21+
ctx: ConstDirectiveStatementContext,
1922
doc: TextDocument,
2023
private readonly documentSettings: DocumentSettings,
2124
private readonly directiveConstants: Map<string, any>) {
2225
super(ctx, doc);
2326

2427
const getNameCtx = () => ctx.constDirectiveName();
2528
this.identifierCapability = new IdentifierCapability(this, getNameCtx);
29+
this.diagnosticCapability = new DiagnosticCapability(this);
2630
}
2731

28-
evaluate(): string {
29-
const vbaExpression = this.context.rule.directiveExpression().vbaExpression();
30-
try {
31-
const tsExpression = transpileVbaToTypescript(vbaExpression, this.documentSettings, this.directiveConstants);
32-
const getExpressionResult = Function('"use strict"; return (' + tsExpression + ')');
33-
return getExpressionResult().toString();
34-
} catch (e) {
35-
// FIXME Add a diagnostic for if this fails.
36-
return '0';
32+
evaluate(): string | number | boolean | Date | null {
33+
const expr = new Expression(this.context.rule.directiveExpression(), this.context.document, this.documentSettings, this.directiveConstants);
34+
const result = expr.evaluate();
35+
36+
Services.logger.log(`Evaluated ${expr.context.text} to ${result}`);
37+
38+
if (result === undefined) {
39+
const diagnostic = new CannotEvaluateExpressionDiagnostic(expr.context.range, expr.context.text);
40+
this.diagnosticCapability.diagnostics.push(diagnostic);
41+
return null;
3742
}
43+
44+
return result;
45+
46+
// const vbaExpression = this.context.rule.directiveExpression().vbaExpression();
47+
// try {
48+
// const tsExpression = transpileVbaToTypescript(vbaExpression, this.documentSettings, this.directiveConstants);
49+
// const getExpressionResult = Function('"use strict"; return (' + tsExpression + ')');
50+
// return getExpressionResult().toString();
51+
// } catch (e) {
52+
// const expressionRange = this.context.rule.directiveExpression().toRange(this.context.document);
53+
// const diagnostic = new CannotEvaluateExpressionDiagnostic(expressionRange, vbaExpression);
54+
// this.diagnosticCapability.diagnostics.push(diagnostic);
55+
// return '0';
56+
// }
3857
}
3958
}
4059

@@ -97,11 +116,11 @@ class CompilerConditionBlock extends BaseRuleSyntaxElement<CompilerConditionalBl
97116
const tsExpression = transpileVbaToTypescript(vbaExpression, this.documentSettings, this.directiveConstants);
98117

99118
// Evaluate the expression and return the result.
100-
const result: boolean = Function('"use strict"; return (' + tsExpression + ')')();
119+
const result = Function('"use strict"; return (' + tsExpression + ')')();
101120
if (!(typeof result === "boolean")) {
102121
// TODO: Return false here instead of throwing
103122
// and return an error diagnostic for the expression.
104-
throw new Error("Expected boolean result.");
123+
throw new Error(`Expected boolean result from ${vbaExpression} => ${tsExpression}.`);
105124
}
106125
return result;
107126
}
@@ -115,34 +134,232 @@ class CompilerConditionBlock extends BaseRuleSyntaxElement<CompilerConditionalBl
115134
}
116135
}
117136

137+
type OperatorContext = OrderOfOps1Context
138+
| OrderOfOps2Context
139+
| OrderOfOps3Context
140+
| OrderOfOps4Context
141+
| OrderOfOps5Context
142+
| OrderOfOps6Context;
143+
144+
class Expression extends BaseRuleSyntaxElement<DirectiveExpressionContext> {
145+
private leftExpr?: Expression;
146+
private rightExpr?: Expression;
147+
private operatorCtx?: OperatorContext;
148+
private isNot = false;
149+
150+
constructor(
151+
ctx: DirectiveExpressionContext,
152+
doc: TextDocument,
153+
private readonly documentSettings: DocumentSettings,
154+
private readonly directiveConstants: Map<string, any>
155+
) {
156+
super(ctx, doc);
157+
158+
// Set the left, right, and operator if we have them.
159+
const expressions = ctx.directiveExpression().map(x =>
160+
new Expression(x, doc, documentSettings, directiveConstants)
161+
);
162+
this.leftExpr = expressions[0];
163+
this.rightExpr = expressions[1];
164+
this.operatorCtx = ctx.orderOfOps1()
165+
?? ctx.orderOfOps2()
166+
?? ctx.orderOfOps3()
167+
?? ctx.orderOfOps4()
168+
?? ctx.orderOfOps5()
169+
?? ctx.orderOfOps6()
170+
?? undefined;
171+
172+
// If we're a 'not' expression, set the flag and the left side only.
173+
const notCtx = ctx.notDirectiveExpression();
174+
if (notCtx) {
175+
this.isNot = true;
176+
const leftExprCtx = notCtx.directiveExpression();
177+
this.leftExpr = new Expression(leftExprCtx, doc, documentSettings, directiveConstants);
178+
}
179+
180+
// Set the expression from the parenthesized expression if we have one.
181+
const parenthExpr = ctx.directiveParenthesizedExpression()?.directiveExpression();
182+
if (parenthExpr) {
183+
this.leftExpr = new Expression(parenthExpr, doc, documentSettings, directiveConstants);
184+
}
185+
}
186+
187+
evaluate(): string | number | boolean | Date | null | undefined {
188+
// Evaluate a not expression.
189+
if (this.isNot && this.leftExpr) {
190+
return !this.leftExpr.evaluate();
191+
}
192+
193+
// Evaluate as left-operator-right.
194+
if (this.leftExpr && this.rightExpr && this.operatorCtx) {
195+
const result = this.performCalculation(this.leftExpr, this.rightExpr, this.operatorCtx);
196+
return result;
197+
}
198+
199+
// Evaluate a literal if we have one.
200+
const ctx = this.context.rule;
201+
const literal = ctx.directiveLiteralExpression();
202+
if (literal) {
203+
return this.evaluateValue(literal);
204+
}
205+
206+
// Evaluate an environment constant if we have one.
207+
const envConstant = ctx.unreservedWord()
208+
?.compilerConstant()
209+
?.getText();
210+
if (envConstant) {
211+
return envConstant.ciEquals(this.documentSettings.environment.os)
212+
|| envConstant.ciEquals(this.documentSettings.environment.version);
213+
}
214+
215+
// Evaluate a user constant if we have one.
216+
const userConstant = ctx.unreservedWord()?.getText();
217+
if (userConstant) {
218+
return this.directiveConstants.get(userConstant);
219+
}
220+
221+
// Otherwise try to return the left expression.
222+
return this.leftExpr?.evaluate();
223+
}
224+
225+
private evaluateValue(literal: DirectiveLiteralExpressionContext) {
226+
// Handle a boolean literal.
227+
const boolCtx = literal.literalIdentifier()?.booleanLiteralIdentifier();
228+
if (boolCtx) return !!boolCtx.TRUE();
229+
230+
// Handle a string literal.
231+
const stringCtx = literal.LITSTRING();
232+
if (stringCtx) return stringCtx.getText();
233+
234+
// Handle a whole number literal.
235+
const intCtx = literal.LITINTEGER();
236+
if (intCtx) return Number.parseInt(intCtx.getText());
237+
238+
// Handle a floating point number literal.
239+
const floatCtx = literal.LITFLOAT();
240+
if (floatCtx) return Number.parseFloat(floatCtx.getText());
241+
242+
// Handle a date literal.
243+
const dateCtx = literal.LITDATE();
244+
if (dateCtx) {
245+
const dateStr = RegExp('#([^#]*)#').exec(dateCtx.getText())?.[1];
246+
return dateStr ? new Date(dateStr) : undefined;
247+
}
248+
249+
// If we get here, we are Null, Empty, or Nothing.
250+
return null;
251+
}
252+
253+
private performCalculation(left: Expression, right: Expression, operation: OperatorContext): number | boolean | string | Date | null | undefined {
254+
const lResult = left.evaluate();
255+
const rResult = right.evaluate();
256+
257+
// Pass on undefined if one or both of our values evaluated to undefined.
258+
if (lResult === undefined || rResult === undefined) return undefined;
259+
260+
// TODO: Test scenarios to account for differences in the way each language coerces values.
261+
const ops = new Map<string, (x: any, y: any) => number | boolean | string | Date | null>();
262+
ops.set('+', (x, y) => x + y);
263+
ops.set('-', (x, y) => x - y);
264+
ops.set('*', (x, y) => x * y);
265+
ops.set('/', (x, y) => x / y);
266+
ops.set('\\', (x, y) => Math.floor(x / y));
267+
ops.set('=', (x, y) => x == y);
268+
ops.set('MOD', (x, y) => x % y);
269+
ops.set('OR', (x, y) => x || y);
270+
ops.set('XOR', (x, y) => x ^ y);
271+
ops.set('AND', (x, y) => x && y);
272+
ops.set('<', (x, y) => x < y);
273+
ops.set('>', (x, y) => x > y);
274+
ops.set('>=', (x, y) => x >= y);
275+
ops.set('<=', (x, y) => x <= y);
276+
ops.set('<>', (x, y) => x != y);
277+
ops.set('&', (x, y) => {
278+
const concat = `${x}${y}`;
279+
if (concat.length > 0 && /^\s*-?(\d+|\d*\.\d+)\s*$/.test(concat)) {
280+
return parseFloat(concat);
281+
} else {
282+
return concat;
283+
}
284+
});
285+
286+
// Like is not a valid operator in constant expressions,
287+
// however, the code may eventually be useful elsewhere.
288+
// ops.set('like', (x, y) => {
289+
// const a = x.toString();
290+
// const b = y.toString();
291+
292+
// if (a === b) {
293+
// return true;
294+
// }
295+
296+
// const pattern = b.replace(/[#?*]/g, (tag: string): string =>
297+
// (new Map<string, string>([
298+
// ['#', '\\d'],
299+
// ['?', '.'],
300+
// ['*', '.*'],
301+
// ])).get(tag) ?? tag);
302+
303+
// return RegExp(pattern).test(a);
304+
// });
305+
306+
ops.set('EQV', (x: any, y: any) => {
307+
const xnor = ~(x ^ y);
308+
const bits = (x > y ? x : y).toString(2).length;
309+
const mask = (1 << bits) - 1;
310+
return xnor & mask;
311+
});
312+
313+
// There's no way this works the same as in VBA.
314+
// Probably need to infer the bits from the variable type.
315+
ops.set('IMP', (x: any, y: any) => {
316+
const imp = ~x | y;
317+
const bits = (x > y ? x : y).toString(2).length;
318+
const mask = (1 << bits) - 1;
319+
return imp & mask;
320+
});
321+
322+
// Perform the operation if it's a known type.
323+
const op = ops.get(operation.getText().toUpperCase());
324+
if (op) return op(lResult, rResult);
325+
}
326+
}
327+
328+
118329
function transpileVbaToTypescript(exp: string, settings: DocumentSettings, directives: Map<string, any>): string {
119330
// Convert the environment constant to boolean.
120-
const envToBooleanText = (opt: string) => {
121-
const isOs = settings.environment.os.toLowerCase() == opt;
122-
const isVer = settings.environment.version.toLowerCase() == opt;
123-
return isOs || isVer ? 'true' : 'false';
124-
};
331+
const envToBooleanText = (opt: string): string => (
332+
opt.ciEquals(settings.environment.os)
333+
|| opt.ciEquals(settings.environment.version)
334+
).toString();
125335

126336
// Set up text replacements map.
127337
const constants = ['vba6', 'vba7', 'mac', 'win16', 'win32', 'win64'];
128338
const replacements = new Map(constants.map(x => [x, envToBooleanText(x)]));
339+
replacements.set('<>', '!=');
129340
replacements.set('or', '||');
341+
replacements.set('xor', '^');
342+
replacements.set('mod', '%');
343+
replacements.set('not', '!');
130344
replacements.set('and', '&&');
131-
replacements.set('not ', '!');
345+
replacements.set('eqv', '');
346+
347+
const getPattern = (x: string) => `(.*)\\b${x}\\b(.*)`;
132348

133349
// Perform language text replacements.
134350
let result = exp;
135351
replacements.forEach((v, k) => {
136-
const regexp = RegExp(`\\b${k}\\b`, 'i');
352+
const regexp = RegExp(getPattern(k), 'i');
137353
if (regexp.test(result)) {
138354
result = result.replace(regexp, v);
139355
}
140356
});
141357

142358
// Perform user directives text replacements.
143359
directives.forEach((v, k) => {
144-
const regexp = RegExp(`\\b${k}\\b`, 'i');
360+
const regexp = RegExp(getPattern(k), 'i');
145361
if (regexp.test(result)) {
362+
Services.logger.log(`Replacing ${k} with ${v}`);
146363
result = result.replace(regexp, v);
147364
}
148365
});

0 commit comments

Comments
 (0)