Skip to content

Commit f0a561c

Browse files
committed
made parser create module declarations even when tree cannot be obtained due to parse exception
1 parent bdb150b commit f0a561c

File tree

1 file changed

+19
-19
lines changed

1 file changed

+19
-19
lines changed

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 19 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -191,8 +191,9 @@ public void ParseComponent(VBComponent vbComponent, TokenStreamRewriter rewriter
191191
commentListener
192192
};
193193

194-
var tree = GetParseTree(vbComponent, listeners, preprocessedModuleBody, qualifiedName);
195-
WalkParseTree(vbComponent, listeners, qualifiedName, tree);
194+
DeclarationSymbolsListener listener;
195+
var tree = GetParseTree(vbComponent, listeners, preprocessedModuleBody, qualifiedName, out listener);
196+
WalkParseTree(listeners, qualifiedName, tree, listener);
196197

197198
State.SetModuleState(vbComponent, ParserState.Parsed);
198199
}
@@ -212,12 +213,26 @@ public void ParseComponent(VBComponent vbComponent, TokenStreamRewriter rewriter
212213
}
213214
}
214215

215-
private IParseTree GetParseTree(VBComponent vbComponent, IParseTreeListener[] listeners, string code, QualifiedModuleName qualifiedName)
216+
private IParseTree GetParseTree(VBComponent vbComponent, IParseTreeListener[] listeners, string code, QualifiedModuleName qualifiedName, out DeclarationSymbolsListener declarationsListener)
216217
{
217218
var commentListener = listeners.OfType<CommentListener>().Single();
218219
ITokenStream stream;
219220

220221
var stopwatch = Stopwatch.StartNew();
222+
if (!_componentAttributes.ContainsKey(vbComponent))
223+
{
224+
_componentAttributes.Add(vbComponent, _attributeParser.Parse(vbComponent));
225+
}
226+
var attributes = _componentAttributes[vbComponent];
227+
228+
// cannot locate declarations in one pass *the way it's currently implemented*,
229+
// because the context in EnterSubStmt() doesn't *yet* have child nodes when the context enters.
230+
// so we need to EnterAmbiguousIdentifier() and evaluate the parent instead - this *might* work.
231+
declarationsListener = new DeclarationSymbolsListener(qualifiedName, Accessibility.Implicit, vbComponent.Type, _state.GetModuleComments(vbComponent), attributes);
232+
233+
declarationsListener.NewDeclaration += declarationsListener_NewDeclaration;
234+
declarationsListener.CreateModuleDeclarations();
235+
221236
var tree = ParseInternal(code, listeners, out stream);
222237
stopwatch.Stop();
223238
if (tree != null)
@@ -237,30 +252,15 @@ private IParseTree GetParseTree(VBComponent vbComponent, IParseTreeListener[] li
237252
private readonly IDictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>> _componentAttributes
238253
= new Dictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>>();
239254

240-
private void WalkParseTree(VBComponent vbComponent, IReadOnlyList<IParseTreeListener> listeners, QualifiedModuleName qualifiedName, IParseTree tree)
255+
private void WalkParseTree(IReadOnlyList<IParseTreeListener> listeners, QualifiedModuleName qualifiedName, IParseTree tree, DeclarationSymbolsListener declarationsListener)
241256
{
242257
var obsoleteCallsListener = listeners.OfType<ObsoleteCallStatementListener>().Single();
243258
var obsoleteLetListener = listeners.OfType<ObsoleteLetStatementListener>().Single();
244259
var emptyStringLiteralListener = listeners.OfType<EmptyStringLiteralListener>().Single();
245260
var argListsWithOneByRefParamListener = listeners.OfType<ArgListWithOneByRefParamListener>().Single();
246261

247-
if (!_componentAttributes.ContainsKey(vbComponent))
248-
{
249-
_componentAttributes.Add(vbComponent, _attributeParser.Parse(vbComponent));
250-
}
251-
var attributes = _componentAttributes[vbComponent];
252-
253-
// cannot locate declarations in one pass *the way it's currently implemented*,
254-
// because the context in EnterSubStmt() doesn't *yet* have child nodes when the context enters.
255-
// so we need to EnterAmbiguousIdentifier() and evaluate the parent instead - this *might* work.
256-
var declarationsListener = new DeclarationSymbolsListener(qualifiedName, Accessibility.Implicit, vbComponent.Type, _state.GetModuleComments(vbComponent), attributes);
257-
258-
declarationsListener.NewDeclaration += declarationsListener_NewDeclaration;
259-
declarationsListener.CreateModuleDeclarations();
260-
261262
var walker = new ParseTreeWalker();
262263
walker.Walk(declarationsListener, tree);
263-
declarationsListener.NewDeclaration -= declarationsListener_NewDeclaration;
264264

265265
_state.ObsoleteCallContexts = obsoleteCallsListener.Contexts.Select(context => new QualifiedContext(qualifiedName, context));
266266
_state.ObsoleteLetContexts = obsoleteLetListener.Contexts.Select(context => new QualifiedContext(qualifiedName, context));

0 commit comments

Comments
 (0)