Skip to content

Commit 19108fe

Browse files
committed
2 parents 48573d5 + 1f244a6 commit 19108fe

File tree

1 file changed

+163
-167
lines changed

1 file changed

+163
-167
lines changed

Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 163 additions & 167 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,8 @@ public class ParseCoordinator : IParseCoordinator
2828
public RubberduckParserState State { get { return _state; } }
2929

3030
private const int _maxDegreeOfParserParallelism = -1;
31+
private const int _maxDegreeOfDeclarationResolverParallelism = -1;
32+
private const int _maxDegreeOfReferenceResolverParallelism = -1;
3133
private const int _maxDegreeOfModuleStateChangeParallelism = -1;
3234

3335
private readonly IDictionary<IVBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>> _componentAttributes
@@ -139,6 +141,25 @@ private void ParseInternal(CancellationTokenSource token)
139141

140142
}
141143

144+
private void ClearComponentStateCacheForTests()
145+
{
146+
foreach (var tree in State.ParseTrees)
147+
{
148+
State.ClearStateCache(tree.Key); // handle potentially removed components without crashing
149+
}
150+
}
151+
152+
private void CleanUpComponentAttributes(List<IVBComponent> components)
153+
{
154+
foreach (var key in _componentAttributes.Keys)
155+
{
156+
if (!components.Contains(key))
157+
{
158+
_componentAttributes.Remove(key);
159+
}
160+
}
161+
}
162+
142163
private void ExecuteCommonParseActivities(List<IVBComponent> toParse, CancellationTokenSource token)
143164
{
144165
SetModuleStates(toParse, ParserState.Pending);
@@ -174,7 +195,17 @@ private void ExecuteCommonParseActivities(List<IVBComponent> toParse, Cancellati
174195

175196
State.SetStatusAndFireStateChanged(this, ParserState.ResolvedDeclarations);
176197

177-
ResolveReferences(token.Token);
198+
if (token.IsCancellationRequested || State.Status >= ParserState.Error)
199+
{
200+
return;
201+
}
202+
203+
ResolveAllReferences(token.Token);
204+
205+
if (token.IsCancellationRequested || State.Status >= ParserState.Error)
206+
{
207+
return;
208+
}
178209

179210
State.RebuildSelectionCache();
180211
}
@@ -194,25 +225,6 @@ private void SetModuleStates(List<IVBComponent> components, ParserState parserSt
194225
State.EvaluateParserState();
195226
}
196227

197-
private void CleanUpComponentAttributes(List<IVBComponent> components)
198-
{
199-
foreach (var key in _componentAttributes.Keys)
200-
{
201-
if (!components.Contains(key))
202-
{
203-
_componentAttributes.Remove(key);
204-
}
205-
}
206-
}
207-
208-
private void ClearComponentStateCacheForTests()
209-
{
210-
foreach (var tree in State.ParseTrees)
211-
{
212-
State.ClearStateCache(tree.Key); // handle potentially removed components without crashing
213-
}
214-
}
215-
216228
private void ParseComponents(List<IVBComponent> components, CancellationToken token)
217229
{
218230
SetModuleStates(components, ParserState.Parsing);
@@ -310,7 +322,7 @@ private void ResolveAllDeclarations(List<IVBComponent> components, CancellationT
310322

311323
var options = new ParallelOptions();
312324
options.CancellationToken = token;
313-
options.MaxDegreeOfParallelism = _maxDegreeOfParserParallelism;
325+
options.MaxDegreeOfParallelism = _maxDegreeOfDeclarationResolverParallelism;
314326
try
315327
{
316328
Parallel.ForEach(components,
@@ -333,12 +345,83 @@ private void ResolveAllDeclarations(List<IVBComponent> components, CancellationT
333345
}
334346
}
335347

348+
private readonly ConcurrentDictionary<string, Declaration> _projectDeclarations = new ConcurrentDictionary<string, Declaration>();
349+
private void ResolveDeclarations(IVBComponent component, IParseTree tree)
350+
{
351+
if (component == null) { return; }
352+
353+
var qualifiedModuleName = new QualifiedModuleName(component);
354+
355+
var stopwatch = Stopwatch.StartNew();
356+
try
357+
{
358+
var project = component.Collection.Parent;
359+
var projectQualifiedName = new QualifiedModuleName(project);
360+
Declaration projectDeclaration;
361+
if (!_projectDeclarations.TryGetValue(projectQualifiedName.ProjectId, out projectDeclaration))
362+
{
363+
projectDeclaration = CreateProjectDeclaration(projectQualifiedName, project);
364+
_projectDeclarations.AddOrUpdate(projectQualifiedName.ProjectId, projectDeclaration, (s, c) => projectDeclaration);
365+
State.AddDeclaration(projectDeclaration);
366+
}
367+
Logger.Debug("Creating declarations for module {0}.", qualifiedModuleName.Name);
368+
369+
var declarationsListener = new DeclarationSymbolsListener(State, qualifiedModuleName, component.Type, State.GetModuleAnnotations(component), State.GetModuleAttributes(component), projectDeclaration);
370+
ParseTreeWalker.Default.Walk(declarationsListener, tree);
371+
foreach (var createdDeclaration in declarationsListener.CreatedDeclarations)
372+
{
373+
State.AddDeclaration(createdDeclaration);
374+
}
375+
}
376+
catch (Exception exception)
377+
{
378+
Logger.Error(exception, "Exception thrown acquiring declarations for '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
379+
State.SetModuleState(component, ParserState.ResolverError);
380+
}
381+
stopwatch.Stop();
382+
Logger.Debug("{0}ms to resolve declarations for component {1}", stopwatch.ElapsedMilliseconds, component.Name);
383+
}
384+
385+
private Declaration CreateProjectDeclaration(QualifiedModuleName projectQualifiedName, IVBProject project)
386+
{
387+
var qualifiedName = projectQualifiedName.QualifyMemberName(project.Name);
388+
var projectId = qualifiedName.QualifiedModuleName.ProjectId;
389+
var projectDeclaration = new ProjectDeclaration(qualifiedName, project.Name, false, project);
390+
391+
var references = new List<ReferencePriorityMap>();
392+
foreach (var item in _projectReferences)
393+
{
394+
if (item.ContainsKey(projectId))
395+
{
396+
references.Add(item);
397+
}
398+
}
399+
400+
foreach (var reference in references)
401+
{
402+
int priority = reference[projectId];
403+
projectDeclaration.AddProjectReference(reference.ReferencedProjectId, priority);
404+
}
405+
return projectDeclaration;
406+
}
407+
336408

337-
private void ResolveReferences(CancellationToken token)
409+
private void ResolveAllReferences(CancellationToken token)
338410
{
411+
var components = State.ParseTrees.Select(kvp => kvp.Key.Component).ToList();
412+
SetModuleStates(components, ParserState.ResolvingReferences);
413+
414+
ExecuteCompilationPasses();
415+
416+
var options = new ParallelOptions();
417+
options.CancellationToken = token;
418+
options.MaxDegreeOfParallelism = _maxDegreeOfReferenceResolverParallelism;
419+
339420
try
340421
{
341-
Task.WaitAll(ResolveReferencesAsync(token));
422+
Parallel.For(0, State.ParseTrees.Count, options,
423+
(index) => ResolveReferences(State.DeclarationFinder, State.ParseTrees[index].Key.Component, State.ParseTrees[index].Value)
424+
);
342425
}
343426
catch (AggregateException exception)
344427
{
@@ -348,6 +431,63 @@ private void ResolveReferences(CancellationToken token)
348431
}
349432
throw;
350433
}
434+
435+
AddUndeclaredVariablesToDeclarations();
436+
437+
State.EvaluateParserState();
438+
}
439+
440+
private void ExecuteCompilationPasses()
441+
{
442+
var passes = new List<ICompilationPass>
443+
{
444+
// This pass has to come first because the type binding resolution depends on it.
445+
new ProjectReferencePass(State.DeclarationFinder),
446+
new TypeHierarchyPass(State.DeclarationFinder, new VBAExpressionParser()),
447+
new TypeAnnotationPass(State.DeclarationFinder, new VBAExpressionParser())
448+
};
449+
passes.ForEach(p => p.Execute());
450+
}
451+
452+
private void ResolveReferences(DeclarationFinder finder, IVBComponent component, IParseTree tree)
453+
{
454+
Debug.Assert(State.GetModuleState(component) == ParserState.ResolvingReferences);
455+
456+
var qualifiedName = new QualifiedModuleName(component);
457+
Logger.Debug("Resolving identifier references in '{0}'... (thread {1})", qualifiedName.Name, Thread.CurrentThread.ManagedThreadId);
458+
459+
var resolver = new IdentifierReferenceResolver(qualifiedName, finder);
460+
var listener = new IdentifierReferenceListener(resolver);
461+
462+
if (!string.IsNullOrWhiteSpace(tree.GetText().Trim()))
463+
{
464+
var walker = new ParseTreeWalker();
465+
try
466+
{
467+
var watch = Stopwatch.StartNew();
468+
walker.Walk(listener, tree);
469+
watch.Stop();
470+
Logger.Debug("Binding resolution done for component '{0}' in {1}ms (thread {2})", component.Name,
471+
watch.ElapsedMilliseconds, Thread.CurrentThread.ManagedThreadId);
472+
473+
//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);
475+
}
476+
catch (Exception exception)
477+
{
478+
Logger.Error(exception, "Exception thrown resolving '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
479+
State.SetModuleState(component, ParserState.ResolverError);
480+
}
481+
}
482+
}
483+
484+
private void AddUndeclaredVariablesToDeclarations()
485+
{
486+
var undeclared = State.DeclarationFinder.Undeclared.ToList();
487+
foreach (var declaration in undeclared)
488+
{
489+
State.AddDeclaration(declaration);
490+
}
351491
}
352492

353493

@@ -405,59 +545,6 @@ private IEnumerable<Declaration> RemovedModuleDeclarations(List<IVBComponent> co
405545
}
406546

407547

408-
private Task[] ResolveReferencesAsync(CancellationToken token)
409-
{
410-
foreach (var kvp in State.ParseTrees)
411-
{
412-
State.SetModuleState(kvp.Key.Component, ParserState.ResolvingReferences);
413-
}
414-
415-
try
416-
{
417-
State.RefreshFinder(_hostApp);
418-
}
419-
catch (Exception exception)
420-
{
421-
Logger.Error(exception);
422-
}
423-
var passes = new List<ICompilationPass>
424-
{
425-
// This pass has to come first because the type binding resolution depends on it.
426-
new ProjectReferencePass(State.DeclarationFinder),
427-
new TypeHierarchyPass(State.DeclarationFinder, new VBAExpressionParser()),
428-
new TypeAnnotationPass(State.DeclarationFinder, new VBAExpressionParser())
429-
};
430-
passes.ForEach(p => p.Execute());
431-
432-
var tasks = new Task[State.ParseTrees.Count];
433-
434-
for (var index = 0; index < State.ParseTrees.Count; index++)
435-
{
436-
var kvp = State.ParseTrees[index];
437-
if (token.IsCancellationRequested)
438-
{
439-
return new Task[0];
440-
}
441-
442-
tasks[index] = Task.Run(() =>
443-
{
444-
State.SetModuleState(kvp.Key.Component, ParserState.ResolvingReferences);
445-
446-
ResolveReferences(State.DeclarationFinder, kvp.Key.Component, kvp.Value);
447-
}, token)
448-
.ContinueWith(t =>
449-
{
450-
var undeclared = State.DeclarationFinder.Undeclared.ToList();
451-
foreach (var declaration in undeclared)
452-
{
453-
State.AddDeclaration(declaration);
454-
}
455-
}, token);
456-
}
457-
458-
return tasks;
459-
}
460-
461548
private void AddBuiltInDeclarations()
462549
{
463550
foreach (var customDeclarationLoader in _customDeclarationLoaders)
@@ -660,97 +747,6 @@ private void UnloadComReference(IReference reference, IReadOnlyList<IVBProject>
660747
}
661748

662749

663-
private readonly ConcurrentDictionary<string, Declaration> _projectDeclarations = new ConcurrentDictionary<string, Declaration>();
664-
private void ResolveDeclarations(IVBComponent component, IParseTree tree)
665-
{
666-
if (component == null) { return; }
667-
668-
var qualifiedModuleName = new QualifiedModuleName(component);
669-
670-
var stopwatch = Stopwatch.StartNew();
671-
try
672-
{
673-
var project = component.Collection.Parent;
674-
var projectQualifiedName = new QualifiedModuleName(project);
675-
Declaration projectDeclaration;
676-
if (!_projectDeclarations.TryGetValue(projectQualifiedName.ProjectId, out projectDeclaration))
677-
{
678-
projectDeclaration = CreateProjectDeclaration(projectQualifiedName, project);
679-
_projectDeclarations.AddOrUpdate(projectQualifiedName.ProjectId, projectDeclaration, (s, c) => projectDeclaration);
680-
State.AddDeclaration(projectDeclaration);
681-
}
682-
Logger.Debug("Creating declarations for module {0}.", qualifiedModuleName.Name);
683-
684-
var declarationsListener = new DeclarationSymbolsListener(State, qualifiedModuleName, component.Type, State.GetModuleAnnotations(component), State.GetModuleAttributes(component), projectDeclaration);
685-
ParseTreeWalker.Default.Walk(declarationsListener, tree);
686-
foreach (var createdDeclaration in declarationsListener.CreatedDeclarations)
687-
{
688-
State.AddDeclaration(createdDeclaration);
689-
}
690-
}
691-
catch (Exception exception)
692-
{
693-
Logger.Error(exception, "Exception thrown acquiring declarations for '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
694-
State.SetModuleState(component, ParserState.ResolverError);
695-
}
696-
stopwatch.Stop();
697-
Logger.Debug("{0}ms to resolve declarations for component {1}", stopwatch.ElapsedMilliseconds, component.Name);
698-
}
699-
700-
private Declaration CreateProjectDeclaration(QualifiedModuleName projectQualifiedName, IVBProject project)
701-
{
702-
var qualifiedName = projectQualifiedName.QualifyMemberName(project.Name);
703-
var projectId = qualifiedName.QualifiedModuleName.ProjectId;
704-
var projectDeclaration = new ProjectDeclaration(qualifiedName, project.Name, false, project);
705-
706-
var references = new List<ReferencePriorityMap>();
707-
foreach (var item in _projectReferences)
708-
{
709-
if (item.ContainsKey(projectId))
710-
{
711-
references.Add(item);
712-
}
713-
}
714-
715-
foreach (var reference in references)
716-
{
717-
int priority = reference[projectId];
718-
projectDeclaration.AddProjectReference(reference.ReferencedProjectId, priority);
719-
}
720-
return projectDeclaration;
721-
}
722-
723-
private void ResolveReferences(DeclarationFinder finder, IVBComponent component, IParseTree tree)
724-
{
725-
Debug.Assert(State.GetModuleState(component) == ParserState.ResolvingReferences);
726-
727-
var qualifiedName = new QualifiedModuleName(component);
728-
Logger.Debug("Resolving identifier references in '{0}'... (thread {1})", qualifiedName.Name, Thread.CurrentThread.ManagedThreadId);
729-
730-
var resolver = new IdentifierReferenceResolver(qualifiedName, finder);
731-
var listener = new IdentifierReferenceListener(resolver);
732-
733-
if (!string.IsNullOrWhiteSpace(tree.GetText().Trim()))
734-
{
735-
var walker = new ParseTreeWalker();
736-
try
737-
{
738-
var watch = Stopwatch.StartNew();
739-
walker.Walk(listener, tree);
740-
watch.Stop();
741-
Logger.Debug("Binding resolution done for component '{0}' in {1}ms (thread {2})", component.Name,
742-
watch.ElapsedMilliseconds, Thread.CurrentThread.ManagedThreadId);
743-
744-
State.SetModuleState(component, ParserState.Ready);
745-
}
746-
catch (Exception exception)
747-
{
748-
Logger.Error(exception, "Exception thrown resolving '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
749-
State.SetModuleState(component, ParserState.ResolverError);
750-
}
751-
}
752-
}
753-
754750
public void Dispose()
755751
{
756752
State.ParseRequest -= ReparseRequested;

0 commit comments

Comments
 (0)