Skip to content

Commit e771718

Browse files
committed
Kill B_CHAR, BF and RESTRICTED_LETTER.
1 parent c18550a commit e771718

File tree

4 files changed

+13
-15
lines changed

4 files changed

+13
-15
lines changed

Rubberduck.Parsing/Grammar/VBALexer.g4

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -21,8 +21,6 @@ lexer grammar VBALexer;
2121
ABS : A B S;
2222
ANY : A N Y;
2323
ARRAY : A R R A Y;
24-
B_CHAR : B; // When trying to define the token `B` for use in the parser, it was being picked up as an IDENTIFIER
25-
BF : B F;
2624
CBOOL : C B O O L;
2725
CBYTE : C B Y T E;
2826
CCUR : C C U R;
@@ -297,6 +295,7 @@ SINGLEQUOTE : '\'';
297295
UNDERSCORE : '_';
298296
WS : [ \t];
299297
GUIDLITERAL : '{' [0-9A-F]+ '-' [0-9A-F]+ '-' [0-9A-F]+ '-' [0-9A-F]+ '-' [0-9A-F]+ '}';
298+
LETTER_RANGE : LETTER WS? MINUS WS? LETTER;
300299
IDENTIFIER : ~[[\]()\r\n\t.,'"|!@#$%^&*\-+:=; 0-9-/\\] ~[[\]()\r\n\t.,'"|!@#$%^&*\-+:=; ]*;
301300
LINE_CONTINUATION : [ \t]* UNDERSCORE [ \t]* '\r'? '\n';
302301
fragment LETTER : [a-zA-Z_äöüÄÖÜ];

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 10 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -286,19 +286,19 @@ defType :
286286
DEFSTR | DEFOBJ | DEFVAR
287287
;
288288
// universalLetterRange must appear before letterRange because they both match the same amount in the case of A-Z but we prefer the universalLetterRange.
289-
letterSpec : singleLetter | universalLetterRange | letterRange;
290-
singleLetter : unrestrictedIdentifier;
289+
// singleLetter must appear at the end to prevent premature bailout
290+
letterSpec : universalLetterRange | letterRange | singleLetter;
291+
292+
// we're purpusefully not actually making sure this is an ASCII letter
293+
// that'd be too much of a hassle with the lexer to get working
294+
singleLetter : {_input.Lt(1).Text.Length == 1}? IDENTIFIER;
291295
// We make a separate universalLetterRange rule because it is treated specially in VBA. This makes it easy for users of the parser
292296
// to identify this case. Quoting MS VBAL:
293297
// "A <universal-letter-range> defines a single implicit declared type for every <IDENTIFIER> within
294298
// a module, even those with a first character that would otherwise fall outside this range if it was
295299
// interpreted as a <letter-range> from A-Z.""
296-
universalLetterRange : upperCaseA whiteSpace? MINUS whiteSpace? upperCaseZ;
297-
upperCaseA : {_input.Lt(1).Text.Equals("A")}? unrestrictedIdentifier;
298-
upperCaseZ : {_input.Lt(1).Text.Equals("Z")}? unrestrictedIdentifier;
299-
letterRange : firstLetter whiteSpace? MINUS whiteSpace? lastLetter;
300-
firstLetter : unrestrictedIdentifier;
301-
lastLetter : unrestrictedIdentifier;
300+
universalLetterRange : {_input.Lt(1).Text.StartsWith("A") && _input.Lt(1).Text.EndsWith("Z")}? LETTER_RANGE;
301+
letterRange : LETTER_RANGE;
302302

303303
doLoopStmt :
304304
DO endOfStatement
@@ -534,7 +534,7 @@ lineSpecialForm : expression whiteSpace (STEP whiteSpace?)? tuple MINUS (STEP wh
534534
circleSpecialForm : (expression whiteSpace? DOT whiteSpace?)? CIRCLE whiteSpace (STEP whiteSpace?)? tuple (whiteSpace? COMMA whiteSpace? expression)+;
535535
scaleSpecialForm : (expression whiteSpace? DOT whiteSpace?)? SCALE whiteSpace tuple whiteSpace? MINUS whiteSpace? tuple;
536536
tuple : LPAREN whiteSpace? expression whiteSpace? COMMA whiteSpace? expression whiteSpace? RPAREN;
537-
lineSpecialFormOption: (B_CHAR | BF);
537+
lineSpecialFormOption : {_input.Lt(1).Text.ToLower().Equals("b") || _input.Lt(1).Text.ToLower().Equals("bf")}? unrestrictedIdentifier;
538538

539539
subscripts : subscript (whiteSpace? COMMA whiteSpace? subscript)*;
540540

@@ -544,7 +544,7 @@ unrestrictedIdentifier : identifier | statementKeyword | markerKeyword;
544544
identifier : typedIdentifier | untypedIdentifier;
545545
untypedIdentifier : identifierValue;
546546
typedIdentifier : untypedIdentifier typeHint;
547-
identifierValue : IDENTIFIER | keyword | foreignName | BF;
547+
identifierValue : IDENTIFIER | keyword | foreignName;
548548
foreignName : L_SQUARE_BRACKET foreignIdentifier* R_SQUARE_BRACKET;
549549
foreignIdentifier : ~(L_SQUARE_BRACKET | R_SQUARE_BRACKET) | foreignName;
550550

@@ -679,7 +679,6 @@ keyword :
679679
| ANY
680680
| ARRAY
681681
| ATTRIBUTE
682-
| B_CHAR
683682
| BEGIN
684683
| BOOLEAN
685684
| BYREF

Rubberduck.Parsing/Preprocessing/VBAConditionalCompilationParser.g4

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -93,7 +93,6 @@ keyword :
9393
| ANY
9494
| ARRAY
9595
| ATTRIBUTE
96-
| B_CHAR
9796
| BEGIN
9897
| BOOLEAN
9998
| BYREF

RubberduckTests/Grammar/VBAParserTests.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using Antlr4.Runtime.Tree.Xpath;
55
using NUnit.Framework;
66
using Rubberduck.Parsing.Grammar;
7+
using Rubberduck.Parsing.Symbols.ParsingExceptions;
78
using System;
89
using System.Collections.Generic;
910
using System.Diagnostics;
@@ -382,7 +383,7 @@ public void TestDefDirectiveSameDefDirectiveMultipleLetterSpec()
382383
[Test]
383384
public void TestDefDirectiveLetterRange()
384385
{
385-
string code = @"DefBool B-C: DefByte Y-X: DefInt I-J: DefLng L-M: DefLngLng N-O: DefLngPtr P-Q: DefCur C-D: DefSng G-H: DefDbl D-E: DefDate T-U: DefStr E-F: DefObj O-P: DefVar V-W";
386+
string code = @"DefBool A-C: DefByte Y-X: DefInt I-J: DefLng L-M: DefLngLng N-O: DefLngPtr P-Q: DefCur C-D: DefSng G-H: DefDbl D-E: DefDate T-U: DefStr E-F: DefObj O-P: DefVar V-W";
386387
var parseResult = Parse(code, PredictionMode.Sll);
387388
AssertTree(parseResult.Item1, parseResult.Item2, "//letterRange", matches => matches.Count == 13);
388389
}

0 commit comments

Comments
 (0)