Skip to content

Commit 6398825

Browse files
authored
Merge pull request #2639 from MDoerner/ReworkParseCoordinatorPart3BugFix
Rework parse coordinator part3 bug fix
2 parents f8632ba + a827ace commit 6398825

File tree

8 files changed

+103
-35
lines changed

8 files changed

+103
-35
lines changed

Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 74 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -78,12 +78,12 @@ private void ReparseRequested(object sender, EventArgs e)
7878
if (!_isTestScope)
7979
{
8080
Cancel();
81-
Task.Run(() => ParseAll(sender, _cancellationTokens[0]));
81+
Task.Run(() => ParseAll(sender, _cancellationTokens[0].Token));
8282
}
8383
else
8484
{
8585
Cancel();
86-
ParseInternal(_cancellationTokens[0]);
86+
ParseInternal(_cancellationTokens[0].Token);
8787
}
8888
}
8989

@@ -108,7 +108,7 @@ private void Cancel(bool createNewTokenSource = true)
108108
public void Parse(CancellationTokenSource token)
109109
{
110110
SetSavedCancellationTokenSource(token);
111-
ParseInternal(token);
111+
ParseInternal(token.Token);
112112
}
113113

114114
private void SetSavedCancellationTokenSource(CancellationTokenSource token)
@@ -125,7 +125,7 @@ private void SetSavedCancellationTokenSource(CancellationTokenSource token)
125125
}
126126
}
127127

128-
private void ParseInternal(CancellationTokenSource token)
128+
private void ParseInternal(CancellationToken token)
129129
{
130130
State.RefreshProjects(_vbe);
131131

@@ -160,9 +160,9 @@ private void CleanUpComponentAttributes(List<IVBComponent> components)
160160
}
161161
}
162162

163-
private void ExecuteCommonParseActivities(List<IVBComponent> toParse, CancellationTokenSource token)
163+
private void ExecuteCommonParseActivities(List<IVBComponent> toParse, CancellationToken token)
164164
{
165-
SetModuleStates(toParse, ParserState.Pending);
165+
SetModuleStates(toParse, ParserState.Pending, token);
166166

167167
SyncComReferences(State.Projects);
168168
RefreshDeclarationFinder();
@@ -178,14 +178,14 @@ private void ExecuteCommonParseActivities(List<IVBComponent> toParse, Cancellati
178178
_projectDeclarations.Clear();
179179
State.ClearBuiltInReferences();
180180

181-
ParseComponents(toParse, token.Token);
181+
ParseComponents(toParse, token);
182182

183183
if (token.IsCancellationRequested || State.Status >= ParserState.Error)
184184
{
185185
return;
186186
}
187187

188-
ResolveAllDeclarations(toParse, token.Token);
188+
ResolveAllDeclarations(toParse, token);
189189
RefreshDeclarationFinder();
190190

191191
if (token.IsCancellationRequested || State.Status >= ParserState.Error)
@@ -200,7 +200,7 @@ private void ExecuteCommonParseActivities(List<IVBComponent> toParse, Cancellati
200200
return;
201201
}
202202

203-
ResolveAllReferences(token.Token);
203+
ResolveAllReferences(token);
204204

205205
if (token.IsCancellationRequested || State.Status >= ParserState.Error)
206206
{
@@ -215,19 +215,23 @@ private void RefreshDeclarationFinder()
215215
State.RefreshFinder(_hostApp);
216216
}
217217

218-
private void SetModuleStates(List<IVBComponent> components, ParserState parserState)
218+
private void SetModuleStates(List<IVBComponent> components, ParserState parserState, CancellationToken token)
219219
{
220220
var options = new ParallelOptions();
221+
options.CancellationToken = token;
221222
options.MaxDegreeOfParallelism = _maxDegreeOfModuleStateChangeParallelism;
222223

223-
Parallel.ForEach(components, options, component => State.SetModuleState(component, parserState, null, false));
224+
Parallel.ForEach(components, options, component => State.SetModuleState(component, parserState, token, null, false));
224225

225-
State.EvaluateParserState();
226+
if (!token.IsCancellationRequested)
227+
{
228+
State.EvaluateParserState();
229+
}
226230
}
227231

228232
private void ParseComponents(List<IVBComponent> components, CancellationToken token)
229233
{
230-
SetModuleStates(components, ParserState.Parsing);
234+
SetModuleStates(components, ParserState.Parsing, token);
231235

232236
var options = new ParallelOptions();
233237
options.CancellationToken = token;
@@ -241,7 +245,7 @@ private void ParseComponents(List<IVBComponent> components, CancellationToken to
241245
{
242246
State.ClearStateCache(component);
243247
var finishedParseTask = FinishedParseComponentTask(component, token);
244-
ProcessComponentParseResults(component, finishedParseTask);
248+
ProcessComponentParseResults(component, finishedParseTask, token);
245249
}
246250
);
247251
}
@@ -286,19 +290,19 @@ private void ParseComponents(List<IVBComponent> components, CancellationToken to
286290
}
287291

288292

289-
private void ProcessComponentParseResults(IVBComponent component, Task<ComponentParseTask.ParseCompletionArgs> finishedParseTask)
293+
private void ProcessComponentParseResults(IVBComponent component, Task<ComponentParseTask.ParseCompletionArgs> finishedParseTask, CancellationToken token)
290294
{
291295
if (finishedParseTask.IsFaulted)
292296
{
293297
//In contrast to the situation in the success scenario, the overall parser state is reevaluated immediately.
294-
State.SetModuleState(component, ParserState.Error, finishedParseTask.Exception.InnerException as SyntaxErrorException);
298+
State.SetModuleState(component, ParserState.Error, token, finishedParseTask.Exception.InnerException as SyntaxErrorException);
295299
}
296300
else if (finishedParseTask.IsCompleted)
297301
{
298302
var result = finishedParseTask.Result;
299303
lock (State)
300304
{
301-
lock (component)
305+
lock (component)
302306
{
303307
State.SetModuleAttributes(component, result.Attributes);
304308
State.AddParseTree(component, result.ParseTree);
@@ -309,7 +313,7 @@ private void ProcessComponentParseResults(IVBComponent component, Task<Component
309313
// This really needs to go last
310314
//It does not reevaluate the overall parer state to avoid concurrent evaluation of all module states and for performance reasons.
311315
//The evaluation has to be triggered manually in the calling procedure.
312-
State.SetModuleState(component, ParserState.Parsed, null, false);
316+
State.SetModuleState(component, ParserState.Parsed, token, null, false); //Note that this is ok because locks allow re-entrancy.
313317
}
314318
}
315319
}
@@ -318,7 +322,7 @@ private void ProcessComponentParseResults(IVBComponent component, Task<Component
318322

319323
private void ResolveAllDeclarations(List<IVBComponent> components, CancellationToken token)
320324
{
321-
SetModuleStates(components, ParserState.ResolvingDeclarations);
325+
SetModuleStates(components, ParserState.ResolvingDeclarations, token);
322326

323327
var options = new ParallelOptions();
324328
options.CancellationToken = token;
@@ -331,7 +335,8 @@ private void ResolveAllDeclarations(List<IVBComponent> components, CancellationT
331335
{
332336
var qualifiedName = new QualifiedModuleName(component);
333337
ResolveDeclarations(qualifiedName.Component,
334-
State.ParseTrees.Find(s => s.Key == qualifiedName).Value);
338+
State.ParseTrees.Find(s => s.Key == qualifiedName).Value,
339+
token);
335340
}
336341
);
337342
}
@@ -346,7 +351,7 @@ private void ResolveAllDeclarations(List<IVBComponent> components, CancellationT
346351
}
347352

348353
private readonly ConcurrentDictionary<string, Declaration> _projectDeclarations = new ConcurrentDictionary<string, Declaration>();
349-
private void ResolveDeclarations(IVBComponent component, IParseTree tree)
354+
private void ResolveDeclarations(IVBComponent component, IParseTree tree, CancellationToken token)
350355
{
351356
if (component == null) { return; }
352357

@@ -376,7 +381,7 @@ private void ResolveDeclarations(IVBComponent component, IParseTree tree)
376381
catch (Exception exception)
377382
{
378383
Logger.Error(exception, "Exception thrown acquiring declarations for '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
379-
State.SetModuleState(component, ParserState.ResolverError);
384+
State.SetModuleState(component, ParserState.ResolverError, token);
380385
}
381386
stopwatch.Stop();
382387
Logger.Debug("{0}ms to resolve declarations for component {1}", stopwatch.ElapsedMilliseconds, component.Name);
@@ -409,18 +414,34 @@ private Declaration CreateProjectDeclaration(QualifiedModuleName projectQualifie
409414
private void ResolveAllReferences(CancellationToken token)
410415
{
411416
var components = State.ParseTrees.Select(kvp => kvp.Key.Component).ToList();
412-
SetModuleStates(components, ParserState.ResolvingReferences);
417+
418+
SetModuleStates(components, ParserState.ResolvingReferences, token);
419+
420+
if (token.IsCancellationRequested)
421+
{
422+
return;
423+
}
413424

414425
ExecuteCompilationPasses();
415426

427+
if (token.IsCancellationRequested)
428+
{
429+
return;
430+
}
431+
416432
var options = new ParallelOptions();
417433
options.CancellationToken = token;
418434
options.MaxDegreeOfParallelism = _maxDegreeOfReferenceResolverParallelism;
419435

436+
if (token.IsCancellationRequested)
437+
{
438+
return;
439+
}
440+
420441
try
421442
{
422443
Parallel.For(0, State.ParseTrees.Count, options,
423-
(index) => ResolveReferences(State.DeclarationFinder, State.ParseTrees[index].Key.Component, State.ParseTrees[index].Value)
444+
(index) => ResolveReferences(State.DeclarationFinder, State.ParseTrees[index].Key, State.ParseTrees[index].Value, token)
424445
);
425446
}
426447
catch (AggregateException exception)
@@ -432,8 +453,21 @@ private void ResolveAllReferences(CancellationToken token)
432453
throw;
433454
}
434455

456+
if (token.IsCancellationRequested)
457+
{
458+
return;
459+
}
460+
435461
AddUndeclaredVariablesToDeclarations();
436462

463+
//This is here and not in the calling method because it has to happen before the ready state is reached.
464+
//RefreshDeclarationFinder(); //Commented out because it breaks the unresolved and undeclared collections.
465+
466+
if (token.IsCancellationRequested)
467+
{
468+
return;
469+
}
470+
437471
State.EvaluateParserState();
438472
}
439473

@@ -449,11 +483,15 @@ private void ExecuteCompilationPasses()
449483
passes.ForEach(p => p.Execute());
450484
}
451485

452-
private void ResolveReferences(DeclarationFinder finder, IVBComponent component, IParseTree tree)
486+
private void ResolveReferences(DeclarationFinder finder, QualifiedModuleName qualifiedName, IParseTree tree, CancellationToken token)
453487
{
454-
Debug.Assert(State.GetModuleState(component) == ParserState.ResolvingReferences);
488+
Debug.Assert(State.GetModuleState(qualifiedName.Component) == ParserState.ResolvingReferences || token.IsCancellationRequested);
489+
490+
if (token.IsCancellationRequested)
491+
{
492+
return;
493+
}
455494

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

459497
var resolver = new IdentifierReferenceResolver(qualifiedName, finder);
@@ -467,16 +505,20 @@ private void ResolveReferences(DeclarationFinder finder, IVBComponent component,
467505
var watch = Stopwatch.StartNew();
468506
walker.Walk(listener, tree);
469507
watch.Stop();
470-
Logger.Debug("Binding resolution done for component '{0}' in {1}ms (thread {2})", component.Name,
508+
Logger.Debug("Binding resolution done for component '{0}' in {1}ms (thread {2})", qualifiedName.Name,
471509
watch.ElapsedMilliseconds, Thread.CurrentThread.ManagedThreadId);
472510

473511
//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);
512+
State.SetModuleState(qualifiedName.Component, ParserState.Ready, token, null, false);
513+
}
514+
catch (OperationCanceledException)
515+
{
516+
throw; //We do not want to set an error state if the exception was just caused by some cancellation.
475517
}
476518
catch (Exception exception)
477519
{
478-
Logger.Error(exception, "Exception thrown resolving '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
479-
State.SetModuleState(component, ParserState.ResolverError);
520+
Logger.Error(exception, "Exception thrown resolving '{0}' (thread {1}).", qualifiedName.Name, Thread.CurrentThread.ManagedThreadId);
521+
State.SetModuleState(qualifiedName.Component, ParserState.ResolverError, token);
480522
}
481523
}
482524
}
@@ -494,7 +536,7 @@ private void AddUndeclaredVariablesToDeclarations()
494536
/// <summary>
495537
/// Starts parsing all components of all unprotected VBProjects associated with the VBE-Instance passed to the constructor of this parser instance.
496538
/// </summary>
497-
private void ParseAll(object requestor, CancellationTokenSource token)
539+
private void ParseAll(object requestor, CancellationToken token)
498540
{
499541
State.RefreshProjects(_vbe);
500542

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -305,6 +305,7 @@ private void OnStateChanged(object requestor, ParserState state = ParserState.Pe
305305
}
306306
public event EventHandler<ParseProgressEventArgs> ModuleStateChanged;
307307

308+
//Never spawn new threads changing module states in the handler! This will cause deadlocks.
308309
private void OnModuleStateChanged(IVBComponent component, ParserState state, ParserState oldState)
309310
{
310311
var handler = ModuleStateChanged;
@@ -315,7 +316,27 @@ private void OnModuleStateChanged(IVBComponent component, ParserState state, Par
315316
}
316317
}
317318

319+
318320
public void SetModuleState(IVBComponent component, ParserState state, SyntaxErrorException parserError = null, bool evaluateOverallState = true)
321+
{
322+
lock (component)
323+
{
324+
SetModuleStateInternal(component, state, parserError, evaluateOverallState);
325+
}
326+
}
327+
328+
public void SetModuleState(IVBComponent component, ParserState state, CancellationToken token, SyntaxErrorException parserError = null, bool evaluateOverallState = true)
329+
{
330+
lock (component)
331+
{
332+
if (!token.IsCancellationRequested)
333+
{
334+
SetModuleStateInternal(component, state, parserError, evaluateOverallState);
335+
}
336+
}
337+
}
338+
339+
public void SetModuleStateInternal(IVBComponent component, ParserState state, SyntaxErrorException parserError = null, bool evaluateOverallState = true)
319340
{
320341
if (AllUserDeclarations.Count > 0)
321342
{
@@ -361,6 +382,7 @@ public void SetModuleState(IVBComponent component, ParserState state, SyntaxErro
361382
}
362383
}
363384

385+
364386
public void EvaluateParserState()
365387
{
366388
lock (_statusLockObject) Status = OverallParserStateFromModuleStates();

Rubberduck.sln

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -254,7 +254,4 @@ Global
254254
GlobalSection(SolutionProperties) = preSolution
255255
HideSolutionNode = FALSE
256256
EndGlobalSection
257-
GlobalSection(Performance) = preSolution
258-
HasPerformanceSessions = true
259-
EndGlobalSection
260257
EndGlobal

RubberduckTests/Binding/MemberAccessTypeBindingTests.cs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -148,6 +148,8 @@ public void NestedMemberAccessExpressions()
148148
var vbe = builder.Build();
149149
var state = Parse(vbe);
150150

151+
Assert.AreEqual(state.Status, ParserState.Ready);
152+
151153
var declaration = state.AllUserDeclarations.Single(d => d.DeclarationType == DeclarationType.Project && d.ProjectName == projectName);
152154
Assert.AreEqual(1, declaration.References.Count(), "Project reference expected");
153155

RubberduckTests/Binding/SimpleNameDefaultBindingTests.cs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -66,6 +66,8 @@ public void EnclosingProjectComesBeforeOtherModuleInEnclosingProject()
6666
var vbe = builder.Build();
6767
var state = Parse(vbe);
6868
var declaration = state.AllUserDeclarations.Single(d => d.DeclarationType == DeclarationType.Project && d.IdentifierName == BindingTargetName);
69+
70+
Assert.AreEqual(state.Status, ParserState.Ready);
6971
Assert.AreEqual(1, declaration.References.Count());
7072
}
7173

RubberduckTests/Binding/SimpleNameProcedurePointerBindingTests.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,7 @@ public void EnclosingProjectComesBeforeOtherProceduralModule()
4949

5050
var declaration = state.AllUserDeclarations.Single(d => d.DeclarationType == DeclarationType.Project && d.IdentifierName == BINDING_TARGET_NAME);
5151

52+
Assert.AreEqual(state.Status, ParserState.Ready);
5253
Assert.AreEqual(1, declaration.References.Count());
5354
}
5455

RubberduckTests/Binding/SimpleNameTypeBindingTests.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -50,6 +50,7 @@ public void EnclosingProjectComesBeforeOtherModuleInEnclosingProject()
5050

5151
var declaration = state.AllUserDeclarations.Single(d => d.DeclarationType == DeclarationType.Project && d.IdentifierName == BINDING_TARGET_NAME);
5252

53+
Assert.AreEqual(state.Status, ParserState.Ready);
5354
Assert.AreEqual(1, declaration.References.Count());
5455
}
5556

RubberduckTests/Grammar/ResolverTests.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2213,6 +2213,7 @@ End Property
22132213
var usages = declaration.References.Where(item =>
22142214
item.ParentNonScoping.IdentifierName == "DoSomething");
22152215

2216+
Assert.AreEqual(state.Status, ParserState.Ready);
22162217
Assert.AreEqual(1, usages.Count());
22172218
}
22182219

0 commit comments

Comments
 (0)