Skip to content

Commit

Permalink
Merge pull request #4661 from comintern/refs
Browse files Browse the repository at this point in the history
Code Explorer Extreme Makeover (for some values of extreme)
  • Loading branch information
bclothier committed Jan 16, 2019
2 parents a926409 + 6df5bde commit f0d4885
Show file tree
Hide file tree
Showing 92 changed files with 6,076 additions and 3,289 deletions.
187 changes: 68 additions & 119 deletions Rubberduck.Core/CodeAnalysis/CodeMetrics/CodeMetricsViewModel.cs
Original file line number Diff line number Diff line change
Expand Up @@ -6,136 +6,93 @@
using System.Collections.Generic;
using System.Collections.ObjectModel;
using Rubberduck.Navigation.CodeExplorer;
using System.Windows;
using Rubberduck.Navigation.Folders;
using Rubberduck.Parsing.UIContext;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;

namespace Rubberduck.CodeAnalysis.CodeMetrics
{
public class CodeMetricsViewModel : ViewModelBase, IDisposable
public sealed class CodeMetricsViewModel : ViewModelBase, IDisposable
{
private readonly RubberduckParserState _state;
private readonly ICodeMetricsAnalyst _analyst;
private readonly FolderHelper _folderHelper;
private readonly IVBE _vbe;
private readonly IUiDispatcher _uiDispatcher;

public CodeMetricsViewModel(RubberduckParserState state, ICodeMetricsAnalyst analyst, FolderHelper folderHelper, IVBE vbe)
public CodeMetricsViewModel(
RubberduckParserState state,
ICodeMetricsAnalyst analyst,
IVBE vbe,
IUiDispatcher uiDispatcher)
{
_state = state;
_analyst = analyst;
_folderHelper = folderHelper;
_state.StateChanged += OnStateChanged;

_analyst = analyst;
_vbe = vbe;
}

private void OnStateChanged(object sender, ParserStateEventArgs e)
{
if (e.State != ParserState.Ready && e.State != ParserState.Error && e.State != ParserState.ResolverError && e.State != ParserState.UnexpectedError)
{
IsBusy = true;
}
_uiDispatcher = uiDispatcher;

if (e.State == ParserState.Ready)
{
UpdateData();
IsBusy = false;
}
OnPropertyChanged(nameof(Projects));
}

if (e.State == ParserState.Error || e.State == ParserState.ResolverError || e.State == ParserState.UnexpectedError)
private bool _unparsed = true;
public bool Unparsed
{
get => _unparsed;
set
{
IsBusy = false;
if (_unparsed == value)
{
return;
}
_unparsed = value;
OnPropertyChanged();
}
}

private void UpdateData()
private void OnStateChanged(object sender, ParserStateEventArgs e)
{
IsBusy = true;

var metricResults = _analyst.GetMetrics(_state);
resultsByDeclaration = metricResults.GroupBy(r => r.Declaration).ToDictionary(g => g.Key, g => g.ToList());
Unparsed = false;
IsBusy = _state.Status != ParserState.Pending && _state.Status <= ParserState.ResolvedDeclarations;

if (Projects == null)
if (e.State != ParserState.ResolvedDeclarations)
{
Projects = new ObservableCollection<CodeExplorerItemViewModel>();
return;
}

IsBusy = _state.Status != ParserState.Pending && _state.Status <= ParserState.ResolvedDeclarations;

var userDeclarations = _state.DeclarationFinder.AllUserDeclarations
.GroupBy(declaration => declaration.ProjectId)
.ToList();

var newProjects = userDeclarations
.Where(grouping => grouping.Any(declaration => declaration.DeclarationType == DeclarationType.Project))
.Select(grouping =>
new CodeExplorerProjectViewModel(_folderHelper,
grouping.SingleOrDefault(declaration => declaration.DeclarationType == DeclarationType.Project),
grouping,
_vbe)).ToList();

UpdateNodes(Projects, newProjects);

Projects = new ObservableCollection<CodeExplorerItemViewModel>(newProjects);

IsBusy = false;
Synchronize(_state.DeclarationFinder.AllUserDeclarations.ToList());
}

private void UpdateNodes(IEnumerable<CodeExplorerItemViewModel> oldList, IEnumerable<CodeExplorerItemViewModel> newList)
private void Synchronize(List<Declaration> declarations)
{
foreach (var item in newList)
{
CodeExplorerItemViewModel oldItem;
var metricResults = _analyst.GetMetrics(_state);
_resultsByDeclaration = metricResults.GroupBy(r => r.Declaration).ToDictionary(g => g.Key, g => g.ToList());

if (item is CodeExplorerCustomFolderViewModel)
{
oldItem = oldList.FirstOrDefault(i => i.Name == item.Name);
}
else
{
oldItem = oldList.FirstOrDefault(i =>
item.QualifiedSelection != null && i.QualifiedSelection != null &&
i.QualifiedSelection.Value.QualifiedName.ProjectId ==
item.QualifiedSelection.Value.QualifiedName.ProjectId &&
i.QualifiedSelection.Value.QualifiedName.ComponentName ==
item.QualifiedSelection.Value.QualifiedName.ComponentName &&
i.QualifiedSelection.Value.Selection == item.QualifiedSelection.Value.Selection);
}
_uiDispatcher.Invoke(() =>
{
var existing = Projects.OfType<CodeExplorerProjectViewModel>().ToList();
if (oldItem != null)
foreach (var project in existing)
{
item.IsExpanded = oldItem.IsExpanded;
item.IsSelected = oldItem.IsSelected;

if (oldItem.Items.Any() && item.Items.Any())
project.Synchronize(declarations);
if (project.Declaration is null)
{
UpdateNodes(oldItem.Items, item.Items);
Projects.Remove(project);
}
}
}
}

public void Dispose()
{
Dispose(true);
GC.SuppressFinalize(this);
}
private bool _isDisposed;
protected virtual void Dispose(bool disposing)
{
if (_isDisposed || !disposing)
{
return;
}
_isDisposed = true;
var adding = declarations.OfType<ProjectDeclaration>().ToList();
_state.StateChanged -= OnStateChanged;
foreach (var project in adding)
{
var model = new CodeExplorerProjectViewModel(project, declarations, _state, _vbe, false);
Projects.Add(model);
model.IsExpanded = true;
}
});
}

private Dictionary<Declaration, List<ICodeMetricResult>> resultsByDeclaration;

private CodeExplorerItemViewModel _selectedItem;
public CodeExplorerItemViewModel SelectedItem
private ICodeExplorerNode _selectedItem;
public ICodeExplorerNode SelectedItem
{
get => _selectedItem;
set
Expand All @@ -150,27 +107,15 @@ public CodeExplorerItemViewModel SelectedItem
}
}

private ObservableCollection<CodeExplorerItemViewModel> _projects;
public ObservableCollection<CodeExplorerItemViewModel> Projects
{
get => _projects;
set
{
_projects = new ObservableCollection<CodeExplorerItemViewModel>(value.OrderBy(o => o.NameWithSignature));
public ObservableCollection<ICodeExplorerNode> Projects { get; } = new ObservableCollection<ICodeExplorerNode>();

OnPropertyChanged();
OnPropertyChanged(nameof(TreeViewVisibility));
}
}

public Visibility TreeViewVisibility => Projects == null || Projects.Count == 0 ? Visibility.Collapsed : Visibility.Visible;

private Dictionary<Declaration, List<ICodeMetricResult>> _resultsByDeclaration;
public ObservableCollection<ICodeMetricResult> Metrics
{
get
{
var results = resultsByDeclaration?.FirstOrDefault(f => f.Key == SelectedItem.GetSelectedDeclaration());
return !results.HasValue || results.Value.Value == null ? new ObservableCollection<ICodeMetricResult>() : new ObservableCollection<ICodeMetricResult>(results.Value.Value);
var results = _resultsByDeclaration?.FirstOrDefault(f => ReferenceEquals(f.Key, SelectedItem.Declaration));
return results?.Value == null ? new ObservableCollection<ICodeMetricResult>() : new ObservableCollection<ICodeMetricResult>(results.Value.Value);
}
}

Expand All @@ -181,23 +126,27 @@ public bool IsBusy
set
{
_isBusy = value;
EmptyUIRefreshMessageVisibility = false;
OnPropertyChanged();
}
}

private bool _emptyUIRefreshMessageVisibility = true;
public bool EmptyUIRefreshMessageVisibility
public void Dispose()
{
get => _emptyUIRefreshMessageVisibility;
set
Dispose(true);
GC.SuppressFinalize(this);
}

private bool _isDisposed;

private void Dispose(bool disposing)
{
if (_isDisposed || !disposing)
{
if (_emptyUIRefreshMessageVisibility != value)
{
_emptyUIRefreshMessageVisibility = value;
OnPropertyChanged();
}
return;
}
_isDisposed = true;

_state.StateChanged -= OnStateChanged;
}
}
}

0 comments on commit f0d4885

Please sign in to comment.