Skip to content

Commit aef8e7f

Browse files
committed
Reparsing a module now cancels a currently running Resolver task
1 parent 5c89ec6 commit aef8e7f

File tree

2 files changed

+9
-6
lines changed

2 files changed

+9
-6
lines changed

Rubberduck.Parsing/VBA/ComponentParseTask.cs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,8 @@ class ComponentParseTask
3131

3232
public ComponentParseTask(VBComponent vbComponent, VBAPreprocessor preprocessor, IAttributeParser attributeParser, TokenStreamRewriter rewriter = null)
3333
{
34+
_attributeParser = attributeParser;
35+
_preprocessor = preprocessor;
3436
_component = vbComponent;
3537
_rewriter = rewriter;
3638
_qualifiedName = new QualifiedModuleName(vbComponent);

Rubberduck.Parsing/VBA/RubberduckParserReimpl.cs

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ public RubberduckParserState State
2828
}
2929

3030
private readonly CancellationTokenSource _central = new CancellationTokenSource();
31+
private readonly CancellationTokenSource _resolverTokenSource; // linked to _central later
3132
private readonly Dictionary<VBComponent, Tuple<Task, CancellationTokenSource>> _currentTasks = new Dictionary<VBComponent, Tuple<Task, CancellationTokenSource>>();
3233

3334
private readonly Dictionary<VBComponent, IParseTree> _parseTrees = new Dictionary<VBComponent, IParseTree>();
@@ -46,6 +47,7 @@ private readonly IDictionary<VBComponent, IDictionary<Tuple<string, DeclarationT
4647

4748
public RubberduckParserReimpl(VBE vbe, RubberduckParserState state, IAttributeParser attributeParser)
4849
{
50+
_resolverTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_central.Token);
4951
_vbe = vbe;
5052
_state = state;
5153
_attributeParser = attributeParser;
@@ -135,12 +137,11 @@ public void Cancel(VBComponent component = null)
135137
}
136138
else
137139
{
140+
_resolverTokenSource.Cancel(false);
138141
Tuple<Task, CancellationTokenSource> result;
139142
if (_currentTasks.TryGetValue(component, out result))
140143
{
141144
result.Item2.Cancel(false);
142-
// should we do this??
143-
//result.Item1.Wait();
144145
}
145146
}
146147
}
@@ -171,7 +172,8 @@ public void ParseComponent(VBComponent component, TokenStreamRewriter rewriter =
171172

172173
public void Resolve(CancellationToken token)
173174
{
174-
Task.Run(() => ResolveInternal(token));
175+
var sharedTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_resolverTokenSource.Token, token);
176+
Task.Run(() => ResolveInternal(sharedTokenSource.Token));
175177
}
176178

177179
private void ResolveInternal(CancellationToken token)
@@ -197,6 +199,7 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
197199
var declarations = new List<Declaration>();
198200
var qualifiedModuleName = new QualifiedModuleName(component);
199201
DeclarationSymbolsListener declarationsListener = new DeclarationSymbolsListener(qualifiedModuleName, Accessibility.Implicit, component.Type, _state.GetModuleComments(component), _state.getModuleAttributes(component));
202+
// TODO: should we unify the API? consider working like the other listeners instead of event-based
200203
declarationsListener.NewDeclaration += (sender, e) => _state.AddDeclaration(e.Declaration);
201204
declarationsListener.CreateModuleDeclarations();
202205

@@ -211,16 +214,14 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
211214
obsoleteLetStatementListener,
212215
emptyStringLiteralListener,
213216
argListWithOneByRefParamListener,
214-
215217
declarationsListener,
216218
}), tree);
217219

218220
// FIXME this are actually (almost) isnpection results.. we should handle them as such
219221
_state.ArgListsWithOneByRefParam = argListWithOneByRefParamListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
220222
_state.EmptyStringLiterals = emptyStringLiteralListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
221223
_state.ObsoleteLetContexts = obsoleteLetStatementListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
222-
_state.ObsoleteCallContexts = obsoleteCallStatementListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
223-
224+
_state.ObsoleteCallContexts = obsoleteCallStatementListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context))
224225
}
225226

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

0 commit comments

Comments
 (0)