Skip to content

Commit 1b757b8

Browse files
committed
Made reference resolver stop on cancellation.
1 parent 5d85113 commit 1b757b8

File tree

1 file changed

+45
-9
lines changed

1 file changed

+45
-9
lines changed

Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 45 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -410,17 +410,32 @@ private void ResolveAllReferences(CancellationToken token)
410410
{
411411
var components = State.ParseTrees.Select(kvp => kvp.Key.Component).ToList();
412412
SetModuleStates(components, ParserState.ResolvingReferences);
413-
413+
414+
if (token.IsCancellationRequested)
415+
{
416+
return;
417+
}
418+
414419
ExecuteCompilationPasses();
415420

421+
if (token.IsCancellationRequested)
422+
{
423+
return;
424+
}
425+
416426
var options = new ParallelOptions();
417427
options.CancellationToken = token;
418428
options.MaxDegreeOfParallelism = _maxDegreeOfReferenceResolverParallelism;
419429

430+
if (token.IsCancellationRequested)
431+
{
432+
return;
433+
}
434+
420435
try
421436
{
422437
Parallel.For(0, State.ParseTrees.Count, options,
423-
(index) => ResolveReferences(State.DeclarationFinder, State.ParseTrees[index].Key.Component, State.ParseTrees[index].Value)
438+
(index) => ResolveReferences(State.DeclarationFinder, State.ParseTrees[index].Key, State.ParseTrees[index].Value, token)
424439
);
425440
}
426441
catch (AggregateException exception)
@@ -432,8 +447,21 @@ private void ResolveAllReferences(CancellationToken token)
432447
throw;
433448
}
434449

450+
if (token.IsCancellationRequested)
451+
{
452+
return;
453+
}
454+
435455
AddUndeclaredVariablesToDeclarations();
436456

457+
//This is here and not in the calling method because it has to happen before the ready state is reached.
458+
//RefreshDeclarationFinder(); //Commented out because it breaks the unresolved and undeclared collections.
459+
460+
if (token.IsCancellationRequested)
461+
{
462+
return;
463+
}
464+
437465
State.EvaluateParserState();
438466
}
439467

@@ -449,11 +477,15 @@ private void ExecuteCompilationPasses()
449477
passes.ForEach(p => p.Execute());
450478
}
451479

452-
private void ResolveReferences(DeclarationFinder finder, IVBComponent component, IParseTree tree)
480+
private void ResolveReferences(DeclarationFinder finder, QualifiedModuleName qualifiedName, IParseTree tree, CancellationToken token)
453481
{
454-
Debug.Assert(State.GetModuleState(component) == ParserState.ResolvingReferences);
482+
Debug.Assert(State.GetModuleState(qualifiedName.Component) == ParserState.ResolvingReferences || token.IsCancellationRequested);
483+
484+
if (token.IsCancellationRequested)
485+
{
486+
return;
487+
}
455488

456-
var qualifiedName = new QualifiedModuleName(component);
457489
Logger.Debug("Resolving identifier references in '{0}'... (thread {1})", qualifiedName.Name, Thread.CurrentThread.ManagedThreadId);
458490

459491
var resolver = new IdentifierReferenceResolver(qualifiedName, finder);
@@ -467,16 +499,20 @@ private void ResolveReferences(DeclarationFinder finder, IVBComponent component,
467499
var watch = Stopwatch.StartNew();
468500
walker.Walk(listener, tree);
469501
watch.Stop();
470-
Logger.Debug("Binding resolution done for component '{0}' in {1}ms (thread {2})", component.Name,
502+
Logger.Debug("Binding resolution done for component '{0}' in {1}ms (thread {2})", qualifiedName.Name,
471503
watch.ElapsedMilliseconds, Thread.CurrentThread.ManagedThreadId);
472504

473505
//Evaluation of the overall status has to be defered to allow processing of undeclared variables before setting the ready state.
474-
State.SetModuleState(component, ParserState.Ready,null,false);
506+
State.SetModuleState(qualifiedName.Component, ParserState.Ready, null, false);
507+
}
508+
catch (OperationCanceledException)
509+
{
510+
throw; //We do not want to set an error state if the exception was just caused by some cancellation.
475511
}
476512
catch (Exception exception)
477513
{
478-
Logger.Error(exception, "Exception thrown resolving '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
479-
State.SetModuleState(component, ParserState.ResolverError);
514+
Logger.Error(exception, "Exception thrown resolving '{0}' (thread {1}).", qualifiedName.Name, Thread.CurrentThread.ManagedThreadId);
515+
State.SetModuleState(qualifiedName.Component, ParserState.ResolverError);
480516
}
481517
}
482518
}

0 commit comments

Comments
 (0)