Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion Rubberduck.Core/AddRemoveReferences/ReferenceModel.cs
Original file line number Diff line number Diff line change
Expand Up @@ -183,7 +183,7 @@ public bool Matches(ReferenceInfo info)
FullPath.Equals(info.FullPath, StringComparison.OrdinalIgnoreCase) ||
FullPath32.Equals(info.FullPath, StringComparison.OrdinalIgnoreCase) ||
FullPath64.Equals(info.FullPath, StringComparison.OrdinalIgnoreCase) ||
Guid.Equals(info.Guid);
!Guid.Equals(Guid.Empty) && Guid.Equals(info.Guid);
}

private void NotifyPropertyChanged([CallerMemberName] string propertyName = "")
Expand Down
16 changes: 7 additions & 9 deletions Rubberduck.Core/CodeAnalysis/CodeMetrics/CodeMetricsViewModel.cs
Original file line number Diff line number Diff line change
Expand Up @@ -54,39 +54,37 @@ private void OnStateChanged(object sender, ParserStateEventArgs e)
Unparsed = false;
IsBusy = _state.Status != ParserState.Pending && _state.Status <= ParserState.ResolvedDeclarations;

if (e.State != ParserState.ResolvedDeclarations)
if (e.State == ParserState.ResolvedDeclarations)
{
return;
Synchronize(_state.DeclarationFinder.AllUserDeclarations);
}

Synchronize(_state.DeclarationFinder.AllUserDeclarations.ToList());
}

private void Synchronize(List<Declaration> declarations)
private void Synchronize(IEnumerable<Declaration> declarations)
{
var metricResults = _analyst.GetMetrics(_state);
_resultsByDeclaration = metricResults.GroupBy(r => r.Declaration).ToDictionary(g => g.Key, g => g.ToList());

_uiDispatcher.Invoke(() =>
{
var updates = declarations.ToList();
var existing = Projects.OfType<CodeExplorerProjectViewModel>().ToList();

foreach (var project in existing)
{
project.Synchronize(declarations);
project.Synchronize(ref updates);
if (project.Declaration is null)
{
Projects.Remove(project);
}
}

var adding = declarations.OfType<ProjectDeclaration>().ToList();
var adding = updates.OfType<ProjectDeclaration>().ToList();

foreach (var project in adding)
{
var model = new CodeExplorerProjectViewModel(project, declarations.Where(proj => proj.ProjectId.Equals(project.ProjectId)).ToList(), _state, _vbe, false);
var model = new CodeExplorerProjectViewModel(project, ref updates, _state, _vbe, false);
Projects.Add(model);
model.IsExpanded = true;
}
});
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -30,12 +30,12 @@ public sealed class CodeExplorerComponentViewModel : CodeExplorerItemViewModel

private readonly IVBE _vbe;

public CodeExplorerComponentViewModel(ICodeExplorerNode parent, Declaration declaration, IEnumerable<Declaration> declarations, IVBE vbe)
public CodeExplorerComponentViewModel(ICodeExplorerNode parent, Declaration declaration, ref List<Declaration> declarations, IVBE vbe)
: base(parent, declaration)
{
_vbe = vbe;
SetName();
AddNewChildren(declarations.ToList());
AddNewChildren(ref declarations);
}

private string _name;
Expand All @@ -54,9 +54,9 @@ public CodeExplorerComponentViewModel(ICodeExplorerNode parent, Declaration decl
public bool IsTestModule => Declaration.DeclarationType == DeclarationType.ProceduralModule
&& Declaration.Annotations.Any(annotation => annotation.AnnotationType == AnnotationType.TestModule);

public override void Synchronize(List<Declaration> updated)
public override void Synchronize(ref List<Declaration> updated)
{
base.Synchronize(updated);
base.Synchronize(ref updated);
if (Declaration is null)
{
return;
Expand All @@ -66,18 +66,23 @@ public override void Synchronize(List<Declaration> updated)
SetName();
}

protected override void AddNewChildren(List<Declaration> updated)
protected override void AddNewChildren(ref List<Declaration> updated)
{
if (updated is null)
{
return;
}

AddChildren(updated.GroupBy(item => item.Scope).SelectMany(grouping =>
grouping.Where(item =>
item.ParentDeclaration != null && item.ParentScope == Declaration.Scope &&
MemberTypes.Contains(item.DeclarationType))
.Select(item => new CodeExplorerMemberViewModel(this, item, grouping))));
var children = updated.Where(declaration =>
!ReferenceEquals(Declaration, declaration) &&
declaration.QualifiedModuleName.Equals(Declaration?.QualifiedModuleName)).ToList();

updated = updated.Except(children.Concat(new [] { Declaration })).ToList();

foreach (var member in children.Where(declaration => MemberTypes.Contains(declaration.DeclarationType)).ToList())
{
AddChild(new CodeExplorerMemberViewModel(this, member, ref children));
}
}

private void SetName()
Expand All @@ -96,8 +101,7 @@ private void SetName()
switch (qualifiedModuleName.ComponentType)
{
case ComponentType.Document:

using (var app = _vbe.HostApplication())
using (var app = _vbe?.HostApplication())
{
var parenthesized = app?.GetDocument(qualifiedModuleName)?.DocumentName ?? string.Empty;
_name = string.IsNullOrEmpty(parenthesized) ? _name : $"{_name} ({parenthesized})";
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@

namespace Rubberduck.Navigation.CodeExplorer
{
[DebuggerDisplay("{Name}")]
[DebuggerDisplay("{" + nameof(Name) + "}")]
public sealed class CodeExplorerCustomFolderViewModel : CodeExplorerItemViewModel
{
private static readonly DeclarationType[] ComponentTypes =
Expand All @@ -26,14 +26,14 @@ public CodeExplorerCustomFolderViewModel(
string name,
string fullPath,
IVBE vbe,
IEnumerable<Declaration> declarations) : base(parent, parent?.Declaration)
ref List<Declaration> declarations) : base(parent, parent?.Declaration)
{
_vbe = vbe;
FolderDepth = parent is CodeExplorerCustomFolderViewModel folder ? folder.FolderDepth + 1 : 1;
FullPath = fullPath?.Trim('"') ?? string.Empty;
Name = name.Replace("\"", string.Empty);

AddNewChildren(declarations.ToList());
AddNewChildren(ref declarations);
}

public override string Name { get; }
Expand Down Expand Up @@ -63,84 +63,78 @@ public override bool IsErrorState

public override bool Filtered => false;

protected override void AddNewChildren(List<Declaration> declarations)
protected override void AddNewChildren(ref List<Declaration> declarations)
{
var children = declarations.Where(declaration => declaration.IsInSubFolder(FullPath)).ToList();
var children = declarations.Where(declaration => declaration.IsInFolderOrSubFolder(FullPath)).ToList();
declarations = declarations.Except(children).ToList();

foreach (var folder in children.GroupBy(declaration => declaration.CustomFolder.SubFolderRoot(FullPath)))
var subFolders = children.Where(declaration => declaration.IsInSubFolder(FullPath)).ToList();

foreach (var folder in subFolders.GroupBy(declaration => declaration.CustomFolder.SubFolderRoot(FullPath)))
{
AddChild(new CodeExplorerCustomFolderViewModel(this, folder.Key, $"{FullPath}.{folder.Key}", _vbe, folder));
foreach (var declaration in folder)
{
declarations.Remove(declaration);
}
var contents = folder.ToList();
AddChild(new CodeExplorerCustomFolderViewModel(this, folder.Key, $"{FullPath}.{folder.Key}", _vbe, ref contents));
}

foreach (var declaration in declarations.Where(child => child.IsInFolder(FullPath)).GroupBy(item => item.ComponentName))
children = children.Except(subFolders).ToList();

foreach (var declaration in children.Where(child => child.IsInFolder(FullPath)).GroupBy(item => item.ComponentName))
{
var moduleName = declaration.Key;
var parent = declarations.SingleOrDefault(item =>
var parent = children.SingleOrDefault(item =>
ComponentTypes.Contains(item.DeclarationType) && item.ComponentName == moduleName);

if (parent is null)
{
continue;
}

var members = declarations.Where(item =>
!ComponentTypes.Contains(item.DeclarationType) && item.ComponentName == moduleName);
var members = children.Where(item =>
!ComponentTypes.Contains(item.DeclarationType) && item.ComponentName == moduleName).ToList();

AddChild(new CodeExplorerComponentViewModel(this, parent, members, _vbe));
declarations.Remove(parent);
AddChild(new CodeExplorerComponentViewModel(this, parent, ref members, _vbe));
}
}

public override void Synchronize(List<Declaration> updated)
public override void Synchronize(ref List<Declaration> updated)
{
SynchronizeChildren(updated);
SynchronizeChildren(ref updated);
}

protected override void SynchronizeChildren(List<Declaration> updated)
protected override void SynchronizeChildren(ref List<Declaration> updated)
{
var declarations = updated.Where(declaration => declaration.IsInFolderOrSubFolder(FullPath)).ToList();

if (!declarations.Any())
var children = updated.Where(declaration => declaration.IsInFolderOrSubFolder(FullPath)).ToList();
updated = updated.Except(children).ToList();

if (!children.Any())
{
Declaration = null;
return;
}

var synchronizing = declarations.ToList();
var subFolders = children.Where(declaration => declaration.IsInSubFolder(FullPath)).ToList();
children = children.Except(subFolders).ToList();

foreach (var subfolder in Children.OfType<CodeExplorerCustomFolderViewModel>().ToList())
{
subfolder.SynchronizeChildren(declarations);
subfolder.SynchronizeChildren(ref subFolders);
if (subfolder.Declaration is null)
{
RemoveChild(subfolder);
continue;
}

var synchronized = synchronizing.Where(child => !declarations.Contains(child)).ToList();
foreach (var declaration in synchronized)
{
updated.Remove(declaration);
}
}

foreach (var child in Children.OfType<CodeExplorerComponentViewModel>().ToList())
{
child.Synchronize(updated);
child.Synchronize(ref children);
if (child.Declaration is null)
{
RemoveChild(child);
continue;
}

updated.Remove(child.Declaration);
}

AddNewChildren(updated);
children = children.Concat(subFolders).ToList();
AddNewChildren(ref children);
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -34,14 +34,16 @@ public override bool IsErrorState
}
}

public virtual void Synchronize(List<Declaration> updated)
public virtual void Synchronize(ref List<Declaration> updated)
{
if (Declaration is null)
{
return;
}

var matching = updated.FirstOrDefault(decl => Declaration.DeclarationType == decl?.DeclarationType && Declaration.QualifiedName.Equals(decl?.QualifiedName));
var matching = updated.FirstOrDefault(decl =>
Declaration.DeclarationType == decl?.DeclarationType &&
Declaration.QualifiedName.Equals(decl.QualifiedName));

if (matching is null)
{
Expand All @@ -51,14 +53,14 @@ public virtual void Synchronize(List<Declaration> updated)

Declaration = matching;
updated.Remove(matching);
SynchronizeChildren(updated);
SynchronizeChildren(ref updated);
}

protected virtual void SynchronizeChildren(List<Declaration> updated)
protected virtual void SynchronizeChildren(ref List<Declaration> updated)
{
foreach (var child in Children.OfType<CodeExplorerItemViewModel>().ToList())
{
child.Synchronize(updated);
child.Synchronize(ref updated);
if (child.Declaration is null)
{
RemoveChild(child);
Expand All @@ -68,9 +70,9 @@ protected virtual void SynchronizeChildren(List<Declaration> updated)
updated.Remove(child.Declaration);
}

AddNewChildren(updated);
AddNewChildren(ref updated);
}

protected abstract void AddNewChildren(List<Declaration> updated);
protected abstract void AddNewChildren(ref List<Declaration> updated);
}
}
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
using System;
using System.Collections.Generic;
using System.Collections.ObjectModel;
using System.Diagnostics.CodeAnalysis;
using System.Globalization;
using System.Linq;
using System.Windows;
Expand Down Expand Up @@ -75,13 +74,12 @@ public virtual string PanelTitle

public virtual string Description => Declaration?.DescriptionString ?? string.Empty;

[SuppressMessage("ReSharper", "ExplicitCallerInfoArgument")]
protected void OnNameChanged()
{
OnPropertyChanged("Name");
OnPropertyChanged("NameWithSignature");
OnPropertyChanged("PanelTitle");
OnPropertyChanged("Description");
OnPropertyChanged(nameof(Name));
OnPropertyChanged(nameof(NameWithSignature));
OnPropertyChanged(nameof(PanelTitle));
OnPropertyChanged(nameof(Description));
}

public virtual QualifiedSelection? QualifiedSelection => Declaration?.QualifiedSelection;
Expand Down Expand Up @@ -232,8 +230,7 @@ public string Filter
}

OnPropertyChanged();
// ReSharper disable once ExplicitCallerInfoArgument
OnPropertyChanged("Filtered");
OnPropertyChanged(nameof(Filtered));
}
}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -7,11 +7,11 @@

namespace Rubberduck.Navigation.CodeExplorer
{
public class CodeExplorerMemberViewModel : CodeExplorerItemViewModel
public sealed class CodeExplorerMemberViewModel : CodeExplorerItemViewModel
{
public CodeExplorerMemberViewModel(ICodeExplorerNode parent, Declaration declaration, IEnumerable<Declaration> declarations) : base(parent, declaration)
public CodeExplorerMemberViewModel(ICodeExplorerNode parent, Declaration declaration, ref List<Declaration> declarations) : base(parent, declaration)
{
AddNewChildren(declarations.ToList());
AddNewChildren(ref declarations);
Name = DetermineMemberName(declaration);
}

Expand Down Expand Up @@ -59,9 +59,9 @@ public override string NameWithSignature
DeclarationType.UserDefinedTypeMember
};

public override void Synchronize(List<Declaration> updated)
public override void Synchronize(ref List<Declaration> updated)
{
base.Synchronize(updated);
base.Synchronize(ref updated);
if (Declaration is null)
{
return;
Expand All @@ -72,15 +72,19 @@ public override void Synchronize(List<Declaration> updated)
OnNameChanged();
}

protected sealed override void AddNewChildren(List<Declaration> updated)
protected override void AddNewChildren(ref List<Declaration> updated)
{
if (updated != null)
if (updated == null)
{
AddChildren(updated
.Where(item =>
SubMemberTypes.Contains(item.DeclarationType) && item.ParentDeclaration.Equals(Declaration))
.Select(item => new CodeExplorerSubMemberViewModel(this, item)));
return;
}

var updates = updated.Where(item =>
SubMemberTypes.Contains(item.DeclarationType) && item.ParentDeclaration.Equals(Declaration)).ToList();

updated = updated.Except(updates.Concat(new[] { Declaration })).ToList();

AddChildren(updates.Select(item => new CodeExplorerSubMemberViewModel(this, item)));
}

public override Comparer<ICodeExplorerNode> SortComparer
Expand Down
Loading