Skip to content

Commit db9c758

Browse files
Andrin Meierretailcoder
authored andcommitted
preprocess code passed on to attribute parser + allow lexpression as … (#1639)
* preprocess code passed on to attribute parser + allow lexpression as attribute name * readd useful comment
1 parent e3131ae commit db9c758

File tree

13 files changed

+117
-90
lines changed

13 files changed

+117
-90
lines changed

RetailCoder.VBE/API/ParserState.cs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,8 @@
66
using Rubberduck.Common;
77
using Rubberduck.Parsing.VBA;
88
using Rubberduck.UI.Command.MenuItems;
9+
using Rubberduck.Parsing.Preprocessing;
10+
using System.Globalization;
911

1012
namespace Rubberduck.API
1113
{
@@ -44,15 +46,13 @@ public sealed class ParserState : IParserState, IDisposable
4446
private const string ProgId = "Rubberduck.ParserState";
4547

4648
private readonly RubberduckParserState _state;
47-
private readonly AttributeParser _attributeParser;
48-
49+
private AttributeParser _attributeParser;
4950
private RubberduckParser _parser;
5051

5152
public ParserState()
5253
{
5354
UiDispatcher.Initialize();
5455
_state = new RubberduckParserState();
55-
_attributeParser = new AttributeParser(new ModuleExporter());
5656

5757
_state.StateChanged += _state_StateChanged;
5858
}
@@ -63,8 +63,9 @@ public void Initialize(VBE vbe)
6363
{
6464
throw new InvalidOperationException("ParserState is already initialized.");
6565
}
66-
67-
_parser = new RubberduckParser(vbe, _state, _attributeParser);
66+
Func<IVBAPreprocessor> preprocessorFactory = () => new VBAPreprocessor(double.Parse(vbe.Version, CultureInfo.InvariantCulture));
67+
_attributeParser = new AttributeParser(new ModuleExporter(), preprocessorFactory);
68+
_parser = new RubberduckParser(vbe, _state, _attributeParser, preprocessorFactory);
6869
}
6970

7071
/// <summary>

RetailCoder.VBE/Root/RubberduckModule.cs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,8 @@
3333
using Rubberduck.UnitTesting;
3434
using Rubberduck.VBEditor.VBEHost;
3535
using NLog;
36+
using Rubberduck.Parsing.Preprocessing;
37+
using System.Globalization;
3638

3739
namespace Rubberduck.Root
3840
{
@@ -94,6 +96,7 @@ public override void Load()
9496

9597
//Bind<TestExplorerModel>().To<StandardModuleTestExplorerModel>().InSingletonScope();
9698
Rebind<IRubberduckParser>().To<RubberduckParser>().InSingletonScope();
99+
Bind<Func<IVBAPreprocessor>>().ToMethod(p => () => new VBAPreprocessor(double.Parse(_vbe.Version, CultureInfo.InvariantCulture)));
97100

98101
_kernel.Rebind<ISearchResultsWindowViewModel>().To<SearchResultsWindowViewModel>().InSingletonScope();
99102
_kernel.Bind<SearchResultPresenterInstanceManager>().ToSelf().InSingletonScope();

Rubberduck.Parsing/Grammar/VBAParser.cs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -831,8 +831,8 @@ public AttributeStmtContext attributeStmt() {
831831
}
832832

833833
public partial class AttributeNameContext : ParserRuleContext {
834-
public UnrestrictedIdentifierContext unrestrictedIdentifier() {
835-
return GetRuleContext<UnrestrictedIdentifierContext>(0);
834+
public LExpressionContext lExpression() {
835+
return GetRuleContext<LExpressionContext>(0);
836836
}
837837
public AttributeNameContext(ParserRuleContext parent, int invokingState)
838838
: base(parent, invokingState)
@@ -861,7 +861,7 @@ public AttributeNameContext attributeName() {
861861
try {
862862
EnterOuterAlt(_localctx, 1);
863863
{
864-
State = 499; unrestrictedIdentifier();
864+
State = 499; lExpression(0);
865865
}
866866
}
867867
catch (RecognitionException re) {
@@ -876,8 +876,8 @@ public AttributeNameContext attributeName() {
876876
}
877877

878878
public partial class AttributeValueContext : ParserRuleContext {
879-
public LiteralExpressionContext literalExpression() {
880-
return GetRuleContext<LiteralExpressionContext>(0);
879+
public ExpressionContext expression() {
880+
return GetRuleContext<ExpressionContext>(0);
881881
}
882882
public AttributeValueContext(ParserRuleContext parent, int invokingState)
883883
: base(parent, invokingState)
@@ -906,7 +906,7 @@ public AttributeValueContext attributeValue() {
906906
try {
907907
EnterOuterAlt(_localctx, 1);
908908
{
909-
State = 501; literalExpression();
909+
State = 501; expression(0);
910910
}
911911
}
912912
catch (RecognitionException re) {
@@ -18325,7 +18325,7 @@ private bool upperCaseA_sempred(UpperCaseAContext _localctx, int predIndex) {
1832518325
"\x3\x2\x2\x2\x1ED\x1EE\x3\x2\x2\x2\x1EE\x1EF\x3\x2\x2\x2\x1EF\x1F1\x5"+
1832618326
"\x12\n\x2\x1F0\x1E9\x3\x2\x2\x2\x1F1\x1F4\x3\x2\x2\x2\x1F2\x1F0\x3\x2"+
1832718327
"\x2\x2\x1F2\x1F3\x3\x2\x2\x2\x1F3\xF\x3\x2\x2\x2\x1F4\x1F2\x3\x2\x2\x2"+
18328-
"\x1F5\x1F6\x5\x126\x94\x2\x1F6\x11\x3\x2\x2\x2\x1F7\x1F8\x5\x150\xA9\x2"+
18328+
"\x1F5\x1F6\x5\x15A\xAE\x2\x1F6\x11\x3\x2\x2\x2\x1F7\x1F8\x5\x14E\xA8\x2"+
1832918329
"\x1F8\x13\x3\x2\x2\x2\x1F9\x1FA\x5\x18\r\x2\x1FA\x1FB\x5\x17C\xBF\x2\x1FB"+
1833018330
"\x1FD\x3\x2\x2\x2\x1FC\x1F9\x3\x2\x2\x2\x1FD\x200\x3\x2\x2\x2\x1FE\x1FC"+
1833118331
"\x3\x2\x2\x2\x1FE\x1FF\x3\x2\x2\x2\x1FF\x15\x3\x2\x2\x2\x200\x1FE\x3\x2"+

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -47,8 +47,8 @@ moduleConfigElement :
4747

4848
moduleAttributes : (attributeStmt endOfStatement)*;
4949
attributeStmt : ATTRIBUTE whiteSpace attributeName whiteSpace? EQ whiteSpace? attributeValue (whiteSpace? COMMA whiteSpace? attributeValue)*;
50-
attributeName : unrestrictedIdentifier;
51-
attributeValue : literalExpression;
50+
attributeName : lExpression;
51+
attributeValue : expression;
5252

5353
moduleDeclarations : (moduleDeclarationsElement endOfStatement)*;
5454

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
namespace Rubberduck.Parsing.Preprocessing
2+
{
3+
public interface IVBAPreprocessor
4+
{
5+
string Execute(string moduleName, string unprocessedCode);
6+
}
7+
}

Rubberduck.Parsing/Preprocessing/VBAPreprocessor.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22

33
namespace Rubberduck.Parsing.Preprocessing
44
{
5-
public sealed class VBAPreprocessor
5+
public sealed class VBAPreprocessor : IVBAPreprocessor
66
{
77
private readonly double _vbaVersion;
88
private readonly VBAPrecompilationParser _parser;

Rubberduck.Parsing/Rubberduck.Parsing.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -120,6 +120,7 @@
120120
<Compile Include="Grammar\VBAParserBaseVisitor.cs" />
121121
<Compile Include="Grammar\VBAParserListener.cs" />
122122
<Compile Include="Grammar\VBAParserVisitor.cs" />
123+
<Compile Include="Preprocessing\IVBAPreprocessor.cs" />
123124
<Compile Include="Preprocessing\VBAConditionalCompilationParser.cs" />
124125
<Compile Include="Preprocessing\VBAConditionalCompilationParserBaseListener.cs" />
125126
<Compile Include="Preprocessing\VBAConditionalCompilationParserBaseVisitor.cs" />

Rubberduck.Parsing/Symbols/Identifier.cs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,16 @@ namespace Rubberduck.Parsing.Symbols
66
{
77
public static class Identifier
88
{
9+
public static string GetName(VBAParser.FunctionNameContext context)
10+
{
11+
return GetName(context.identifier());
12+
}
13+
14+
public static string GetName(VBAParser.SubroutineNameContext context)
15+
{
16+
return GetName(context.identifier());
17+
}
18+
919
public static string GetName(VBAParser.UnrestrictedIdentifierContext context)
1020
{
1121
if (context.identifier() != null)

Rubberduck.Parsing/VBA/AttributeParser.cs

Lines changed: 62 additions & 66 deletions
Original file line numberDiff line numberDiff line change
@@ -1,23 +1,27 @@
1-
using System;
2-
using System.Collections.Generic;
3-
using System.IO;
4-
using System.Linq;
5-
using Antlr4.Runtime;
6-
using Antlr4.Runtime.Misc;
1+
using Antlr4.Runtime;
72
using Antlr4.Runtime.Tree;
83
using Microsoft.Vbe.Interop;
4+
using NLog;
95
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.Parsing.Preprocessing;
107
using Rubberduck.Parsing.Symbols;
8+
using System;
9+
using System.Collections.Generic;
10+
using System.IO;
11+
using System.Linq;
1112

1213
namespace Rubberduck.Parsing.VBA
1314
{
1415
public class AttributeParser : IAttributeParser
1516
{
1617
private readonly IModuleExporter _exporter;
18+
private readonly Func<IVBAPreprocessor> _preprocessorFactory;
19+
private static readonly Logger _logger = LogManager.GetCurrentClassLogger();
1720

18-
public AttributeParser(IModuleExporter exporter)
21+
public AttributeParser(IModuleExporter exporter, Func<IVBAPreprocessor> preprocessorFactory)
1922
{
2023
_exporter = exporter;
24+
_preprocessorFactory = preprocessorFactory;
2125
}
2226

2327
/// <summary>
@@ -32,26 +36,28 @@ public IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(VBComponent
3236
// a document component without any code wouldn't be exported (file would be empty anyway).
3337
return new Dictionary<Tuple<string, DeclarationType>, Attributes>();
3438
}
35-
3639
var code = File.ReadAllText(path);
3740
File.Delete(path);
38-
3941
var type = component.Type == vbext_ComponentType.vbext_ct_StdModule
4042
? DeclarationType.ProceduralModule
4143
: DeclarationType.ClassModule;
44+
var preprocessor = _preprocessorFactory();
45+
string preprocessed;
46+
try
47+
{
48+
preprocessed = preprocessor.Execute(component.Name, code);
49+
}
50+
catch (VBAPreprocessorException ex)
51+
{
52+
_logger.Error(ex, "Preprocessing failed while preparing attribute parsing for module {0}. Trying without preprocessing.", component.Name);
53+
preprocessed = code;
54+
}
4255
var listener = new AttributeListener(Tuple.Create(component.Name, type));
43-
44-
var stream = new AntlrInputStream(code);
45-
var lexer = new VBALexer(stream);
46-
var tokens = new CommonTokenStream(lexer);
47-
var parser = new VBAParser(tokens);
48-
4956
// parse tree isn't usable for declarations because
5057
// line numbers are offset due to module header and attributes
5158
// (these don't show up in the VBE, that's why we're parsing an exported file)
52-
var tree = parser.startRule();
53-
ParseTreeWalker.Default.Walk(listener, tree);
54-
59+
ITokenStream tokenStream;
60+
new VBAModuleParser().Parse(component.Name, preprocessed, new IParseTreeListener[] { listener }, out tokenStream);
5561
return listener.Attributes;
5662
}
5763

@@ -76,56 +82,21 @@ public IDictionary<Tuple<string, DeclarationType>, Attributes> Attributes
7682

7783
public override void ExitModuleAttributes(VBAParser.ModuleAttributesContext context)
7884
{
79-
_attributes.Add(_currentScope, _currentScopeAttributes);
80-
}
81-
82-
private static readonly IReadOnlyDictionary<Type, DeclarationType> ScopingContextTypes =
83-
new Dictionary<Type, DeclarationType>
84-
{
85-
{typeof(VBAParser.SubStmtContext), DeclarationType.Procedure},
86-
{typeof(VBAParser.FunctionStmtContext), DeclarationType.Function},
87-
{typeof(VBAParser.PropertyGetStmtContext), DeclarationType.PropertyGet},
88-
{typeof(VBAParser.PropertyLetStmtContext), DeclarationType.PropertyLet},
89-
{typeof(VBAParser.PropertySetStmtContext), DeclarationType.PropertySet}
90-
};
91-
92-
public override void EnterSubroutineName(VBAParser.SubroutineNameContext context)
93-
{
94-
if (ParserRuleContextHelper.HasParent<VBAParser.SubStmtContext>(context))
85+
if (_currentScopeAttributes.Any())
9586
{
96-
_currentScope = Tuple.Create(context.GetText(), DeclarationType.Procedure);
97-
}
98-
else if (ParserRuleContextHelper.HasParent<VBAParser.PropertyGetStmtContext>(context))
99-
{
100-
_currentScope = Tuple.Create(context.GetText(), DeclarationType.PropertyGet);
101-
}
102-
}
103-
104-
public override void EnterFunctionName(VBAParser.FunctionNameContext context)
105-
{
106-
if (ParserRuleContextHelper.HasParent<VBAParser.FunctionStmtContext>(context))
107-
{
108-
_currentScope = Tuple.Create(context.identifier().GetText(), DeclarationType.Function);
109-
}
110-
else if (ParserRuleContextHelper.HasParent<VBAParser.PropertyLetStmtContext>(context))
111-
{
112-
_currentScope = Tuple.Create(context.identifier().GetText(), DeclarationType.PropertyLet);
113-
}
114-
else if (ParserRuleContextHelper.HasParent<VBAParser.PropertySetStmtContext>(context))
115-
{
116-
_currentScope = Tuple.Create(context.identifier().GetText(), DeclarationType.PropertySet);
87+
_attributes.Add(_currentScope, _currentScopeAttributes);
11788
}
11889
}
11990

12091
public override void EnterSubStmt(VBAParser.SubStmtContext context)
12192
{
12293
_currentScopeAttributes = new Attributes();
123-
_currentScope = Tuple.Create(context.subroutineName().GetText(), DeclarationType.Procedure);
94+
_currentScope = Tuple.Create(Identifier.GetName(context.subroutineName()), DeclarationType.Procedure);
12495
}
12596

12697
public override void ExitSubStmt(VBAParser.SubStmtContext context)
12798
{
128-
if (!string.IsNullOrEmpty(_currentScope.Item1) && _currentScopeAttributes.Any())
99+
if (_currentScopeAttributes.Any())
129100
{
130101
_attributes.Add(_currentScope, _currentScopeAttributes);
131102
}
@@ -134,12 +105,12 @@ public override void ExitSubStmt(VBAParser.SubStmtContext context)
134105
public override void EnterFunctionStmt(VBAParser.FunctionStmtContext context)
135106
{
136107
_currentScopeAttributes = new Attributes();
137-
_currentScope = Tuple.Create(context.functionName().identifier().GetText(), DeclarationType.Function);
108+
_currentScope = Tuple.Create(Identifier.GetName(context.functionName()), DeclarationType.Function);
138109
}
139110

140111
public override void ExitFunctionStmt(VBAParser.FunctionStmtContext context)
141112
{
142-
if (!string.IsNullOrEmpty(_currentScope.Item1) && _currentScopeAttributes.Any())
113+
if (_currentScopeAttributes.Any())
143114
{
144115
_attributes.Add(_currentScope, _currentScopeAttributes);
145116
}
@@ -148,12 +119,12 @@ public override void ExitFunctionStmt(VBAParser.FunctionStmtContext context)
148119
public override void EnterPropertyGetStmt(VBAParser.PropertyGetStmtContext context)
149120
{
150121
_currentScopeAttributes = new Attributes();
151-
_currentScope = Tuple.Create(context.functionName().identifier().GetText(), DeclarationType.PropertyGet);
122+
_currentScope = Tuple.Create(Identifier.GetName(context.functionName()), DeclarationType.PropertyGet);
152123
}
153124

154125
public override void ExitPropertyGetStmt(VBAParser.PropertyGetStmtContext context)
155126
{
156-
if (!string.IsNullOrEmpty(_currentScope.Item1) && _currentScopeAttributes.Any())
127+
if (_currentScopeAttributes.Any())
157128
{
158129
_attributes.Add(_currentScope, _currentScopeAttributes);
159130
}
@@ -162,12 +133,12 @@ public override void ExitPropertyGetStmt(VBAParser.PropertyGetStmtContext contex
162133
public override void EnterPropertyLetStmt(VBAParser.PropertyLetStmtContext context)
163134
{
164135
_currentScopeAttributes = new Attributes();
165-
_currentScope = Tuple.Create(context.subroutineName().GetText(), DeclarationType.PropertyLet);
136+
_currentScope = Tuple.Create(Identifier.GetName(context.subroutineName()), DeclarationType.PropertyLet);
166137
}
167138

168139
public override void ExitPropertyLetStmt(VBAParser.PropertyLetStmtContext context)
169140
{
170-
if (!string.IsNullOrEmpty(_currentScope.Item1) && _currentScopeAttributes.Any())
141+
if (_currentScopeAttributes.Any())
171142
{
172143
_attributes.Add(_currentScope, _currentScopeAttributes);
173144
}
@@ -176,24 +147,49 @@ public override void ExitPropertyLetStmt(VBAParser.PropertyLetStmtContext contex
176147
public override void EnterPropertySetStmt(VBAParser.PropertySetStmtContext context)
177148
{
178149
_currentScopeAttributes = new Attributes();
179-
_currentScope = Tuple.Create(context.subroutineName().GetText(), DeclarationType.PropertySet);
150+
_currentScope = Tuple.Create(Identifier.GetName(context.subroutineName()), DeclarationType.PropertySet);
180151
}
181152

182153
public override void ExitPropertySetStmt(VBAParser.PropertySetStmtContext context)
183154
{
184-
if (!string.IsNullOrEmpty(_currentScope.Item1) && _currentScopeAttributes.Any())
155+
if (_currentScopeAttributes.Any())
185156
{
186157
_attributes.Add(_currentScope, _currentScopeAttributes);
187158
}
188159
}
189160

190161
public override void ExitAttributeStmt(VBAParser.AttributeStmtContext context)
191162
{
192-
var name = context.attributeName().GetText().Trim();
163+
// We assume attributes can either be simple names (VB_Name) or, if they are inside procedures, member access expressions
164+
// (e.g. Foo.VB_UserMemId = 0)
165+
var expr = context.attributeName().lExpression();
166+
string name;
167+
if (expr is VBAParser.SimpleNameExprContext)
168+
{
169+
name = ((VBAParser.SimpleNameExprContext)expr).identifier().GetText();
170+
}
171+
else
172+
{
173+
// Turns "Foo.VB_ProcData.VB_Invoke_Func" into "VB_ProcData.VB_Invoke_Func",
174+
// because we are not interested in the subroutine name Foo.
175+
name = GetAttributeNameWithoutProcedureName((VBAParser.MemberAccessExprContext)expr);
176+
}
193177
var values = context.attributeValue().Select(e => e.GetText().Replace("\"", string.Empty)).ToList();
194178
_currentScopeAttributes.Add(name, values);
195179
}
196180

181+
private string GetAttributeNameWithoutProcedureName(VBAParser.MemberAccessExprContext expr)
182+
{
183+
string name = expr.unrestrictedIdentifier().GetText();
184+
// The simple name expression represents the procedure's name.
185+
// We don't want that one though so we simply ignore it.
186+
if (expr.lExpression() is VBAParser.SimpleNameExprContext)
187+
{
188+
return name;
189+
}
190+
return string.Format("{0}.{1}", GetAttributeNameWithoutProcedureName((VBAParser.MemberAccessExprContext)expr.lExpression()), name);
191+
}
192+
197193
public override void ExitModuleConfigElement(VBAParser.ModuleConfigElementContext context)
198194
{
199195
var name = context.unrestrictedIdentifier().GetText();

0 commit comments

Comments
 (0)