Skip to content

Commit 5550154

Browse files
committed
Some optimization
1 parent b8756b1 commit 5550154

File tree

2 files changed

+54
-27
lines changed

2 files changed

+54
-27
lines changed

Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 44 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,7 @@ public class ParseCoordinator : IParseCoordinator
3131
private const int _maxDegreeOfDeclarationResolverParallelism = -1;
3232
private const int _maxDegreeOfReferenceResolverParallelism = -1;
3333
private const int _maxDegreeOfModuleStateChangeParallelism = -1;
34+
private const int _maxDegreeOfReferenceRemovalParallelism = -1;
3435
private const int _maxReferenceLoadingConcurrency = -1;
3536

3637
private readonly IDictionary<IVBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>> _componentAttributes
@@ -185,7 +186,7 @@ private void ClearComponentStateCacheForTests()
185186
}
186187
}
187188

188-
private void CleanUpComponentAttributes(List<IVBComponent> components)
189+
private void CleanUpComponentAttributes(ICollection<IVBComponent> components)
189190
{
190191
foreach (var key in _componentAttributes.Keys)
191192
{
@@ -214,8 +215,9 @@ private void ExecuteCommonParseActivities(List<IVBComponent> toParse, Cancellati
214215

215216
token.ThrowIfCancellationRequested();
216217

217-
var toResolveReferences = ModulesForWhichToResolveReferences(toParse);
218-
PerformPreParseCleanup(toParse, toResolveReferences);
218+
var modulesToParse = toParse.Select(component => new QualifiedModuleName(component)).ToHashSet();
219+
var toResolveReferences = ModulesForWhichToResolveReferences(modulesToParse);
220+
PerformPreParseCleanup(modulesToParse, toResolveReferences, token);
219221

220222
ParseComponents(toParse, token);
221223

@@ -268,28 +270,48 @@ private void SetModuleStates(List<IVBComponent> components, ParserState parserSt
268270
}
269271
}
270272

271-
private ICollection<QualifiedModuleName> ModulesForWhichToResolveReferences(List<IVBComponent> toParse)
273+
private ICollection<QualifiedModuleName> ModulesForWhichToResolveReferences(ICollection<QualifiedModuleName> modulesToParse)
272274
{
273-
var toResolveReferences = toParse.Select(component => new QualifiedModuleName(component)).ToHashSet();
274-
foreach (var qmn in toParse.Select(component => new QualifiedModuleName(component)))
275+
var toResolveReferences = modulesToParse.ToHashSet();
276+
foreach (var qmn in modulesToParse)
275277
{
276278
toResolveReferences.UnionWith(State.ModulesReferencing(qmn));
277279
}
278280
return toResolveReferences;
279281
}
280282

281-
private void PerformPreParseCleanup(List<IVBComponent> toParse, ICollection<QualifiedModuleName> toResolveReferences)
283+
private void PerformPreParseCleanup(ICollection<QualifiedModuleName> modulesToParse, ICollection<QualifiedModuleName> toResolveReferences, CancellationToken token)
282284
{
283-
ClearModuleToModuleReferences(toParse);
284-
State.RemoveAllReferencesBy(toResolveReferences);
285+
ClearModuleToModuleReferences(modulesToParse);
286+
RemoveAllReferencesBy(toResolveReferences, modulesToParse, State.DeclarationFinder, token); //All declarations on the modulesToParse get destroyed anyway.
285287
_projectDeclarations.Clear();
286288
}
287289

288-
private void ClearModuleToModuleReferences(List<IVBComponent> toClear)
290+
private void ClearModuleToModuleReferences(ICollection<QualifiedModuleName> toClear)
289291
{
290-
foreach (var component in toClear)
292+
foreach (var qmn in toClear)
291293
{
292-
State.ClearModuleToModuleReferencesFromModule(new QualifiedModuleName(component));
294+
State.ClearModuleToModuleReferencesFromModule(qmn);
295+
}
296+
}
297+
298+
//This doesn not live on the RubberduckParserState to keep concurrency haanlding out of it.
299+
public void RemoveAllReferencesBy(ICollection<QualifiedModuleName> referencesFromToRemove, ICollection<QualifiedModuleName> modulesNotNeedingReferenceRemoval, DeclarationFinder finder, CancellationToken token)
300+
{
301+
var referencedModulesNeedingReferenceRemoval = State.ModulesReferencedBy(referencesFromToRemove).Where(qmn => !modulesNotNeedingReferenceRemoval.Contains(qmn));
302+
303+
var options = new ParallelOptions();
304+
options.CancellationToken = token;
305+
options.MaxDegreeOfParallelism = _maxDegreeOfReferenceRemovalParallelism;
306+
307+
Parallel.ForEach(referencedModulesNeedingReferenceRemoval, options, qmn => RemoveReferences(finder.Members(qmn), referencesFromToRemove));
308+
}
309+
310+
private void RemoveReferences(IEnumerable<Declaration> declarations, ICollection<QualifiedModuleName> referencesFromToRemove)
311+
{
312+
foreach (var declaration in declarations)
313+
{
314+
declaration.RemoveReferencesFrom(referencesFromToRemove);
293315
}
294316
}
295317

@@ -688,7 +710,7 @@ private void ParseAllInternal(object requestor, CancellationToken token)
688710

689711
token.ThrowIfCancellationRequested();
690712

691-
var componentsRemoved = CleanUpRemovedComponents(components);
713+
var componentsRemoved = CleanUpRemovedComponents(components, token);
692714

693715
token.ThrowIfCancellationRequested();
694716

@@ -721,21 +743,24 @@ private void ParseAllInternal(object requestor, CancellationToken token)
721743
/// Clears state cache of removed components.
722744
/// Returns whether components have been removed.
723745
/// </summary>
724-
private bool CleanUpRemovedComponents(List<IVBComponent> components)
746+
private bool CleanUpRemovedComponents(ICollection<IVBComponent> components, CancellationToken token)
725747
{
726748
var removedModuledecalrations = RemovedModuleDeclarations(components);
727749
var componentRemoved = removedModuledecalrations.Any();
728750
var removedModules = removedModuledecalrations.Select(declaration => declaration.QualifiedName.QualifiedModuleName).ToHashSet();
729-
State.RemoveAllReferencesBy(removedModules);
730-
foreach (var qmn in removedModules)
751+
if (removedModules.Any())
731752
{
732-
State.ClearModuleToModuleReferencesFromModule(qmn);
733-
State.ClearStateCache(qmn);
753+
RemoveAllReferencesBy(removedModules, removedModules, State.DeclarationFinder, token);
754+
foreach (var qmn in removedModules)
755+
{
756+
State.ClearModuleToModuleReferencesFromModule(qmn);
757+
State.ClearStateCache(qmn);
758+
}
734759
}
735760
return componentRemoved;
736761
}
737762

738-
private IEnumerable<Declaration> RemovedModuleDeclarations(List<IVBComponent> components)
763+
private IEnumerable<Declaration> RemovedModuleDeclarations(ICollection<IVBComponent> components)
739764
{
740765
var moduleDeclarations = State.AllUserDeclarations.Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Module));
741766
var componentKeys = components.Select(component => new { name = component.Name, projectId = component.Collection.Parent.HelpFile }).ToHashSet();

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 10 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -795,14 +795,6 @@ public void ClearAllReferences()
795795
}
796796
}
797797

798-
public void RemoveAllReferencesBy(ICollection<QualifiedModuleName> referencesFromToRemove)
799-
{
800-
foreach (var declaration in AllDeclarations)
801-
{
802-
declaration.RemoveReferencesFrom(referencesFromToRemove);
803-
}
804-
}
805-
806798
public bool ClearStateCache(IVBComponent component, bool notifyStateChanged = false)
807799
{
808800
return component != null && ClearStateCache(new QualifiedModuleName(component), notifyStateChanged);
@@ -1189,6 +1181,16 @@ public HashSet<QualifiedModuleName> ModulesReferencedBy(QualifiedModuleName refe
11891181
return new HashSet<QualifiedModuleName>(referencingModuleState.HasReferenceToModule.Keys);
11901182
}
11911183

1184+
public HashSet<QualifiedModuleName> ModulesReferencedBy(IEnumerable<QualifiedModuleName> referencingModules)
1185+
{
1186+
var referencedModules = new HashSet<QualifiedModuleName>();
1187+
foreach (var referencingModule in referencedModules)
1188+
{
1189+
referencedModules.UnionWith(ModulesReferencedBy(referencingModule));
1190+
}
1191+
return referencedModules;
1192+
}
1193+
11921194
public HashSet<QualifiedModuleName> ModulesReferencing(QualifiedModuleName referencedModule)
11931195
{
11941196
ModuleState referencedModuleState;

0 commit comments

Comments
 (0)