Skip to content

Commit e3a82e0

Browse files
committed
Merge branch 'next' into ExtractComponentsFromQMNsSecondTry
2 parents 2e518b4 + 20ffa00 commit e3a82e0

File tree

3 files changed

+31
-9
lines changed

3 files changed

+31
-9
lines changed

Rubberduck.Parsing/Grammar/VBALexer.g4

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -295,8 +295,7 @@ SINGLEQUOTE : '\'';
295295
UNDERSCORE : '_';
296296
WS : [ \t];
297297
GUIDLITERAL : '{' [0-9A-F]+ '-' [0-9A-F]+ '-' [0-9A-F]+ '-' [0-9A-F]+ '-' [0-9A-F]+ '}';
298-
LETTER_RANGE : LETTER WS? MINUS WS? LETTER;
299-
IDENTIFIER : ~[[\]()\r\n\t.,'"|!@#$%^&*\-+:=; 0-9-/\\] ~[[\]()\r\n\t.,'"|!@#$%^&*\-+:=; ]*;
298+
IDENTIFIER : ~[[\]()\r\n\t.,'"|!@#$%^&*\-+:=; 0-9-/\\-] ~[[\]()\r\n\t.,'"|!@#$%^&*\-+:=; -]*;
300299
LINE_CONTINUATION : [ \t]* UNDERSCORE [ \t]* '\r'? '\n';
301300
fragment LETTER : [a-zA-Z_äöüÄÖÜ];
302301
fragment DIGIT : [0-9];

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,8 @@ parser grammar VBAParser;
2121

2222
options { tokenVocab = VBALexer; }
2323

24+
@header { using System.Text.RegularExpressions; }
25+
2426
startRule : module EOF;
2527

2628
module :
@@ -289,16 +291,17 @@ defType :
289291
// singleLetter must appear at the end to prevent premature bailout
290292
letterSpec : universalLetterRange | letterRange | singleLetter;
291293

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;
294+
singleLetter : {_input.Lt(1).Text.Length == 1 && Regex.Match(_input.Lt(1).Text, @"[a-zA-Z]").Success}? IDENTIFIER;
295+
295296
// We make a separate universalLetterRange rule because it is treated specially in VBA. This makes it easy for users of the parser
296297
// to identify this case. Quoting MS VBAL:
297298
// "A <universal-letter-range> defines a single implicit declared type for every <IDENTIFIER> within
298299
// a module, even those with a first character that would otherwise fall outside this range if it was
299300
// interpreted as a <letter-range> from A-Z.""
300-
universalLetterRange : {_input.Lt(1).Text.StartsWith("A") && _input.Lt(1).Text.EndsWith("Z")}? LETTER_RANGE;
301-
letterRange : LETTER_RANGE;
301+
universalLetterRange : {_input.Lt(1).Text.Equals("A") && _input.Lt(3).Text.Equals("Z")}? IDENTIFIER MINUS IDENTIFIER;
302+
303+
letterRange : singleLetter MINUS singleLetter;
304+
302305

303306
doLoopStmt :
304307
DO endOfStatement

RubberduckTests/Grammar/VBAParserTests.cs

Lines changed: 22 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
using Antlr4.Runtime.Tree.Xpath;
55
using NUnit.Framework;
66
using Rubberduck.Parsing.Grammar;
7-
using Rubberduck.Parsing.Symbols.ParsingExceptions;
87
using System;
98
using System.Collections.Generic;
109
using System.Diagnostics;
@@ -392,7 +391,7 @@ public void TestDefDirectiveLetterRange()
392391
[Test]
393392
public void TestDefDirectiveUniversalLetterRange()
394393
{
395-
string code = @"DefBool A - Z";
394+
string code = @"DefBool A-Z";
396395
var parseResult = Parse(code);
397396
AssertTree(parseResult.Item1, parseResult.Item2, "//universalLetterRange");
398397
}
@@ -2136,6 +2135,26 @@ End Sub
21362135
AssertTree(parseResult.Item1, parseResult.Item2, "//attributeStmt", matches => matches.Count == 1);
21372136
}
21382137

2138+
[Category("Parser")]
2139+
[Test]
2140+
public void SubtractionExpressionsAreNoLetterRanges()
2141+
{
2142+
const string code = @"
2143+
Public Sub Foo()
2144+
Dim a As Long
2145+
Dim b As Long
2146+
Dim z As Long
2147+
a = 1
2148+
b = 2
2149+
z = a-b
2150+
b = a-z
2151+
End Sub
2152+
";
2153+
var parseResult = Parse(code);
2154+
AssertTree(parseResult.Item1, parseResult.Item2, "//letterRange", matches => matches.Count == 0);
2155+
AssertTree(parseResult.Item1, parseResult.Item2, "//universalLetterRange", matches => matches.Count == 0);
2156+
}
2157+
21392158
private Tuple<VBAParser, ParserRuleContext> Parse(string code, PredictionMode predictionMode = null)
21402159
{
21412160
var stream = new AntlrInputStream(code);
@@ -2157,6 +2176,7 @@ private Tuple<VBAParser, ParserRuleContext> Parse(string code, PredictionMode pr
21572176
{
21582177
// If SLL fails we want to get notified ASAP so we can fix it, that's why we don't retry using LL.
21592178
// If LL mode fails, we're done.
2179+
21602180
throw;
21612181
}
21622182

0 commit comments

Comments
 (0)