Skip to content

Commit 13087a4

Browse files
author
Scott Dennison
committed
Modify grammar and introduce base class to reduce target language dependence of grammar.
1 parent c337646 commit 13087a4

File tree

4 files changed

+127
-14
lines changed

4 files changed

+127
-14
lines changed
Lines changed: 34 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,34 @@
1+
using Antlr4.Runtime;
2+
3+
namespace Rubberduck.Parsing.Grammar
4+
{
5+
public abstract class VBABaseLexer : Lexer
6+
{
7+
public VBABaseLexer(ICharStream input) : base(input) { }
8+
9+
#region Semantic predicate helper methods
10+
protected int LA(int i)
11+
{
12+
return _input.La(i);
13+
}
14+
15+
protected bool IsChar(int actual, char expected)
16+
{
17+
return (char)actual == expected;
18+
}
19+
20+
protected bool IsChar(int actual, params char[] expectedOptions)
21+
{
22+
char actualAsChar = (char)actual;
23+
foreach (char expected in expectedOptions)
24+
{
25+
if (actualAsChar == expected)
26+
{
27+
return true;
28+
}
29+
}
30+
return false;
31+
}
32+
#endregion
33+
}
34+
}
Lines changed: 79 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,79 @@
1+
using Antlr4.Runtime;
2+
using System;
3+
using System.Text.RegularExpressions;
4+
5+
namespace Rubberduck.Parsing.Grammar
6+
{
7+
public abstract class VBABaseParser : Parser
8+
{
9+
public VBABaseParser(ITokenStream input) : base(input) { }
10+
11+
#region Semantic predicate helper methods
12+
protected int LA(int i)
13+
{
14+
return _input.La(i);
15+
}
16+
17+
protected IToken LT(int i)
18+
{
19+
return _input.Lt(i);
20+
}
21+
22+
protected string Text(IToken token)
23+
{
24+
return token.Text;
25+
}
26+
27+
protected bool MatchesRegex(string text, string pattern)
28+
{
29+
return Regex.Match(text,pattern).Success;
30+
}
31+
32+
protected bool EqualsStringIgnoringCase(string actual, string expected)
33+
{
34+
return actual.Equals(expected,StringComparison.OrdinalIgnoreCase);
35+
}
36+
37+
protected bool EqualsStringIgnoringCase(string actual, params string[] expectedOptions)
38+
{
39+
foreach (string expected in expectedOptions)
40+
{
41+
if (actual.Equals(expected,StringComparison.OrdinalIgnoreCase))
42+
{
43+
return true;
44+
}
45+
}
46+
return false;
47+
}
48+
49+
protected bool EqualsString(string actual, string expected)
50+
{
51+
return actual.Equals(expected,StringComparison.Ordinal);
52+
}
53+
54+
protected bool EqualsString(string actual, params string[] expectedOptions)
55+
{
56+
foreach (string expected in expectedOptions)
57+
{
58+
if (actual.Equals(expected,StringComparison.Ordinal))
59+
{
60+
return true;
61+
}
62+
}
63+
return false;
64+
}
65+
66+
protected bool IsTokenType(int actual, params int[] expectedOptions)
67+
{
68+
foreach (int expected in expectedOptions)
69+
{
70+
if (actual == expected)
71+
{
72+
return true;
73+
}
74+
}
75+
return false;
76+
}
77+
#endregion
78+
}
79+
}

Rubberduck.Parsing/Grammar/VBALexer.g4

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,9 @@
1717

1818
lexer grammar VBALexer;
1919

20+
options {
21+
superClass = VBABaseLexer;
22+
}
2023

2124
ABS : A B S;
2225
ANY : A N Y;
@@ -305,11 +308,7 @@ IDENTIFIER : ~[[\](){}\r\n\t.,'"|!@#$%^&*\-+:=; 0-9-/\\-] ~[[\](){}\r\n\t.,'"|!
305308
LINE_CONTINUATION : [ \t]+ UNDERSCORE [ \t]* '\r'? '\n' WS_NOT_FOLLOWED_BY_LINE_CONTINUATION*;
306309
// The following rule is needed in order to capture hex literals without format prefixes which start with a digit. Needed for VBForm resources.
307310
BARE_HEX_LITERAL : [0-9] [0-9a-fA-F]*;
308-
fragment WS_NOT_FOLLOWED_BY_LINE_CONTINUATION : [ \t] {(char)_input.La(1) != '_'
309-
|| ((char)_input.La(2) != '\r'
310-
&& (char)_input.La(2) != '\n'
311-
&& (char)_input.La(2) != '\t'
312-
&& (char)_input.La(2) != ' ')}?;
311+
fragment WS_NOT_FOLLOWED_BY_LINE_CONTINUATION : [ \t] {!IsChar(LA(1),'_') || !IsChar(LA(2),'\r','\n','\t',' ')}?;
313312
fragment LETTER : [a-zA-Z_äöüÄÖÜ];
314313
fragment DIGIT : [0-9];
315314
fragment LETTERORDIGIT : [a-zA-Z0-9_äöüÄÖÜ];

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 10 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -19,9 +19,10 @@
1919

2020
parser grammar VBAParser;
2121

22-
options { tokenVocab = VBALexer; }
23-
24-
@header { using System.Text.RegularExpressions; }
22+
options {
23+
tokenVocab = VBALexer;
24+
superClass = VBABaseParser;
25+
}
2526

2627
startRule : module EOF;
2728

@@ -321,14 +322,14 @@ defType :
321322
// singleLetter must appear at the end to prevent premature bailout
322323
letterSpec : universalLetterRange | letterRange | singleLetter;
323324

324-
singleLetter : {_input.Lt(1).Text.Length == 1 && Regex.Match(_input.Lt(1).Text, @"[a-zA-Z]").Success}? IDENTIFIER;
325+
singleLetter : {MatchesRegex(Text(LT(1)),"^[a-zA-Z]$")}? IDENTIFIER;
325326

326327
// We make a separate universalLetterRange rule because it is treated specially in VBA. This makes it easy for users of the parser
327328
// to identify this case. Quoting MS VBAL:
328329
// "A <universal-letter-range> defines a single implicit declared type for every <IDENTIFIER> within
329330
// a module, even those with a first character that would otherwise fall outside this range if it was
330331
// interpreted as a <letter-range> from A-Z.""
331-
universalLetterRange : {_input.Lt(1).Text.Equals("A") && _input.Lt(3).Text.Equals("Z")}? IDENTIFIER MINUS IDENTIFIER;
332+
universalLetterRange : {EqualsString(Text(LT(1)),"A") && EqualsString(Text(LT(3)),"Z")}? IDENTIFIER MINUS IDENTIFIER;
332333

333334
letterRange : singleLetter MINUS singleLetter;
334335

@@ -571,22 +572,22 @@ circleSpecialForm : (expression whiteSpace? DOT whiteSpace?)? CIRCLE whiteSpace
571572
scaleSpecialForm : (expression whiteSpace? DOT whiteSpace?)? SCALE whiteSpace tuple whiteSpace? MINUS whiteSpace? tuple;
572573
pSetSpecialForm : (expression whiteSpace? DOT whiteSpace?)? PSET (whiteSpace STEP)? whiteSpace? tuple whiteSpace? (COMMA whiteSpace? expression)?;
573574
tuple : LPAREN whiteSpace? expression whiteSpace? COMMA whiteSpace? expression whiteSpace? RPAREN;
574-
lineSpecialFormOption : {_input.Lt(1).Text.ToLower().Equals("b") || _input.Lt(1).Text.ToLower().Equals("bf")}? unrestrictedIdentifier;
575+
lineSpecialFormOption : {EqualsStringIgnoringCase(Text(LT(1)),"b","bf")}? unrestrictedIdentifier;
575576

576577
subscripts : subscript (whiteSpace? COMMA whiteSpace? subscript)*;
577578

578579
subscript : (expression whiteSpace TO whiteSpace)? expression;
579580

580581
unrestrictedIdentifier : identifier | statementKeyword | markerKeyword;
581-
legalLabelIdentifier : { !(new[]{DOEVENTS,END,CLOSE,ELSE,LOOP,NEXT,RANDOMIZE,REM,RESUME,RETURN,STOP,WEND}).Contains(_input.La(1))}? identifier | markerKeyword;
582+
legalLabelIdentifier : { !IsTokenType(LA(1),DOEVENTS,END,CLOSE,ELSE,LOOP,NEXT,RANDOMIZE,REM,RESUME,RETURN,STOP,WEND)}? identifier | markerKeyword;
582583
//The predicate in the following rule has been introduced to lessen the problem that VBA uses the same characters used as type hints in other syntactical constructs,
583584
//e.g. in the bang notation (see withDictionaryAccessExpr). Generally, it is not legal to have an identifier or opening bracket follow immediately after a type hint.
584585
//The first part of the predicate tries to exclude these two situations. Unfortunately, predicates have to be at the start of a rule. So, an assumption about the number
585586
//of tokens in the identifier is made. All untypedIdentifers not a foreignNames consist of exactly one token and a typedIdentifier is an untyped one followed by a typeHint,
586587
//again a single token. So, in the majority of situations, the third token is the token following the potential type hint.
587588
//For foreignNames, no assumption can be made because they consist of a pair of brackets containing arbitrarily many tokens.
588589
//That is why the second part of the predicate looks at the first character in order to determine whether the identifier is a foreignName.
589-
identifier : {_input.La(3) != IDENTIFIER && _input.La(3) != L_SQUARE_BRACKET || _input.La(1) == L_SQUARE_BRACKET}? typedIdentifier
590+
identifier : {!IsTokenType(LA(3),IDENTIFIER,L_SQUARE_BRACKET) || IsTokenType(LA(1),L_SQUARE_BRACKET)}? typedIdentifier
590591
| untypedIdentifier;
591592
untypedIdentifier : identifierValue;
592593
typedIdentifier : untypedIdentifier typeHint;
@@ -614,7 +615,7 @@ complexType :
614615
fieldLength : MULT whiteSpace? (numberLiteral | identifierValue);
615616

616617
//Statement labels can only appear at the start of a line.
617-
statementLabelDefinition : {_input.La(-1) == NEWLINE || _input.La(-1) == LINE_CONTINUATION}? (combinedLabels | identifierStatementLabel | standaloneLineNumberLabel);
618+
statementLabelDefinition : {IsTokenType(LA(-1),NEWLINE,LINE_CONTINUATION)}? (combinedLabels | identifierStatementLabel | standaloneLineNumberLabel);
618619
identifierStatementLabel : legalLabelIdentifier whiteSpace? COLON;
619620
standaloneLineNumberLabel :
620621
lineNumberLabel whiteSpace? COLON

0 commit comments

Comments
 (0)