Skip to content

Commit 024bcb5

Browse files
committed
Changed the way the ParseTree is walked for declarations. Fixes two-hundred-something tests
1 parent c8700fe commit 024bcb5

File tree

2 files changed

+55
-34
lines changed

2 files changed

+55
-34
lines changed

Rubberduck.Parsing/VBA/ComponentParseTask.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,10 @@ public void Start(CancellationToken token)
4545
var code = RewriteAndPreprocess();
4646
token.ThrowIfCancellationRequested();
4747

48+
var attributes = _attributeParser.Parse(_component);
49+
50+
token.ThrowIfCancellationRequested();
51+
4852
// temporal coupling... comments must be acquired before we walk the parse tree for declarations
4953
// otherwise none of the annotations get associated to their respective Declaration
5054
var commentListener = new CommentListener();
@@ -61,10 +65,6 @@ public void Start(CancellationToken token)
6165
var comments = QualifyAndUnionComments(_qualifiedName, commentListener.Comments, commentListener.RemComments);
6266
token.ThrowIfCancellationRequested();
6367

64-
var attributes = _attributeParser.Parse(_component);
65-
66-
token.ThrowIfCancellationRequested();
67-
6868
ParseCompleted.Invoke(this, new ParseCompletionArgs
6969
{
7070
ParseTree = tree,

Rubberduck.Parsing/VBA/RubberduckParserReimpl.cs

Lines changed: 51 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,8 @@ private void StateOnStateChanged(object sender, EventArgs e)
6666
if (args.State == ParserState.Parsed)
6767
{
6868
Debug.WriteLine("(handling OnStateChanged) Starting resolver task");
69-
Task.Run(() => Resolve(_central.Token));
69+
Resolve(_central.Token); // Tests expect this to be synchronous
70+
//Task.Run(() => Resolve(_central.Token));
7071
}
7172
}
7273

@@ -87,12 +88,23 @@ private void ReparseRequested(object sender, EventArgs e)
8788

8889
public void Parse()
8990
{
90-
try
91+
var projects = _vbe.VBProjects
92+
.Cast<VBProject>()
93+
.Where(project => project.Protection == vbext_ProjectProtection.vbext_pp_none);
94+
95+
var components = projects.SelectMany(p => p.VBComponents.Cast<VBComponent>());
96+
// invalidation cleanup should go into ParseAsync?
97+
foreach (var invalidated in _componentAttributes.Keys.Except(components))
9198
{
92-
ParseAll();
93-
} catch (Exception e)
99+
_componentAttributes.Remove(invalidated);
100+
}
101+
102+
foreach (var vbComponent in components)
94103
{
95-
Debug.WriteLine(e);
104+
while (!_state.ClearDeclarations(vbComponent)) { }
105+
106+
// expects synchronous parse :/
107+
ParseComponent(vbComponent);
96108
}
97109
}
98110

@@ -185,6 +197,7 @@ private void ParseAsyncInternal(VBComponent component, CancellationToken token,
185197
_state.AddParseTree(component, e.ParseTree);
186198
_state.AddTokenStream(component, e.Tokens);
187199
_state.SetModuleComments(component, e.Comments);
200+
188201
// This really needs to go last
189202
_state.SetModuleState(component, ParserState.Parsed);
190203
};
@@ -200,7 +213,9 @@ public void ParseComponent(VBComponent component, TokenStreamRewriter rewriter =
200213
public void Resolve(CancellationToken token)
201214
{
202215
var sharedTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_resolverTokenSource.Token, token);
203-
Task.Run(() => ResolveInternal(sharedTokenSource.Token));
216+
// tests expect this to be synchronous :/
217+
//Task.Run(() => ResolveInternal(sharedTokenSource.Token));
218+
ResolveInternal(sharedTokenSource.Token);
204219
}
205220

206221
private void ResolveInternal(CancellationToken token)
@@ -220,37 +235,43 @@ private void ResolveInternal(CancellationToken token)
220235

221236
private void ResolveDeclarations(VBComponent component, IParseTree tree)
222237
{
223-
// cannot locate declarations in one pass *the way it's currently implemented*,
224-
// because the context in EnterSubStmt() doesn't *yet* have child nodes when the context enters.
225-
// so we need to EnterAmbiguousIdentifier() and evaluate the parent instead - this *might* work.
226-
var declarations = new List<Declaration>();
227238
var qualifiedModuleName = new QualifiedModuleName(component);
228-
DeclarationSymbolsListener declarationsListener = new DeclarationSymbolsListener(qualifiedModuleName, Accessibility.Implicit, component.Type, _state.GetModuleComments(component), _state.getModuleAttributes(component));
229-
// TODO: should we unify the API? consider working like the other listeners instead of event-based
230-
declarationsListener.NewDeclaration += (sender, e) => _state.AddDeclaration(e.Declaration);
231-
declarationsListener.CreateModuleDeclarations();
232239

233240
var obsoleteCallStatementListener = new ObsoleteCallStatementListener();
234241
var obsoleteLetStatementListener = new ObsoleteLetStatementListener();
235242
var emptyStringLiteralListener = new EmptyStringLiteralListener();
236243
var argListWithOneByRefParamListener = new ArgListWithOneByRefParamListener();
244+
245+
try
246+
{
247+
var walker = new ParseTreeWalker();
248+
walker.Walk(new CombinedParseTreeListener(new IParseTreeListener[]{
249+
obsoleteCallStatementListener,
250+
obsoleteLetStatementListener,
251+
emptyStringLiteralListener,
252+
argListWithOneByRefParamListener,
253+
}), tree);
254+
// FIXME this are actually (almost) isnpection results.. we should handle them as such
255+
_state.ArgListsWithOneByRefParam = argListWithOneByRefParamListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
256+
_state.EmptyStringLiterals = emptyStringLiteralListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
257+
_state.ObsoleteLetContexts = obsoleteLetStatementListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
258+
_state.ObsoleteCallContexts = obsoleteCallStatementListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
259+
260+
// cannot locate declarations in one pass *the way it's currently implemented*,
261+
// because the context in EnterSubStmt() doesn't *yet* have child nodes when the context enters.
262+
// so we need to EnterAmbiguousIdentifier() and evaluate the parent instead - this *might* work.
263+
DeclarationSymbolsListener declarationsListener = new DeclarationSymbolsListener(qualifiedModuleName, Accessibility.Implicit, component.Type, _state.GetModuleComments(component), _state.getModuleAttributes(component));
264+
// TODO: should we unify the API? consider working like the other listeners instead of event-based
265+
declarationsListener.NewDeclaration += (sender, e) => _state.AddDeclaration(e.Declaration);
266+
declarationsListener.CreateModuleDeclarations();
267+
// rewalk parse tree for second declaration level
268+
walker.Walk(declarationsListener, tree);
269+
} catch (Exception exception)
270+
{
271+
Debug.Print("Exception thrown resolving '{0}' (thread {2}): {1}", component.Name, exception, Thread.CurrentThread.ManagedThreadId);
272+
_state.SetModuleState(component, ParserState.ResolverError);
273+
}
237274

238-
// FIXME account for errors here
239-
240-
var walker = new ParseTreeWalker();
241-
walker.Walk(new CombinedParseTreeListener(new IParseTreeListener[]{
242-
obsoleteCallStatementListener,
243-
obsoleteLetStatementListener,
244-
emptyStringLiteralListener,
245-
argListWithOneByRefParamListener,
246-
declarationsListener,
247-
}), tree);
248-
249-
// FIXME this are actually (almost) isnpection results.. we should handle them as such
250-
_state.ArgListsWithOneByRefParam = argListWithOneByRefParamListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
251-
_state.EmptyStringLiterals = emptyStringLiteralListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
252-
_state.ObsoleteLetContexts = obsoleteLetStatementListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
253-
_state.ObsoleteCallContexts = obsoleteCallStatementListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
254275
}
255276

256277
private void ResolveReferences(DeclarationFinder finder, VBComponent component, IParseTree tree)

0 commit comments

Comments
 (0)