Skip to content

Commit

Permalink
Merge pull request #4718 from comintern/next
Browse files Browse the repository at this point in the history
Code Explorer folder hotfix.
  • Loading branch information
comintern committed Jan 17, 2019
2 parents f0d4885 + 8ab45d8 commit 64ae145
Show file tree
Hide file tree
Showing 9 changed files with 695 additions and 480 deletions.
Expand Up @@ -84,7 +84,7 @@ private void Synchronize(List<Declaration> declarations)
foreach (var project in adding)
{
var model = new CodeExplorerProjectViewModel(project, declarations, _state, _vbe, false);
var model = new CodeExplorerProjectViewModel(project, declarations.Where(proj => proj.ProjectId.Equals(project.ProjectId)).ToList(), _state, _vbe, false);
Projects.Add(model);
model.IsExpanded = true;
}
Expand Down
@@ -1,4 +1,5 @@
using System.Collections.Generic;
using System.Diagnostics;
using System.Linq;
using Rubberduck.Navigation.Folders;
using Rubberduck.Parsing.Symbols;
Expand All @@ -7,6 +8,7 @@

namespace Rubberduck.Navigation.CodeExplorer
{
[DebuggerDisplay("{Name}")]
public sealed class CodeExplorerCustomFolderViewModel : CodeExplorerItemViewModel
{
private static readonly DeclarationType[] ComponentTypes =
Expand All @@ -27,8 +29,8 @@ public sealed class CodeExplorerCustomFolderViewModel : CodeExplorerItemViewMode
IEnumerable<Declaration> declarations) : base(parent, parent?.Declaration)
{
_vbe = vbe;

FullPath = fullPath ?? string.Empty;
FolderDepth = parent is CodeExplorerCustomFolderViewModel folder ? folder.FolderDepth + 1 : 1;
FullPath = fullPath?.Trim('"') ?? string.Empty;
Name = name.Replace("\"", string.Empty);

AddNewChildren(declarations.ToList());
Expand All @@ -44,6 +46,11 @@ public sealed class CodeExplorerCustomFolderViewModel : CodeExplorerItemViewMode

public string FolderAttribute => $"@Folder(\"{FullPath.Replace("\"", string.Empty)}\")";

/// <summary>
/// One-based depth in the folder hierarchy.
/// </summary>
public int FolderDepth { get; }

public override QualifiedSelection? QualifiedSelection => null;

public override bool IsErrorState
Expand All @@ -58,18 +65,20 @@ public override bool IsErrorState

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

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

var components = declarations.Except(subfolders).ToList();

foreach (var component in components.GroupBy(item => item.ComponentName))
foreach (var declaration in declarations.GroupBy(item => item.ComponentName))
{
var moduleName = component.Key;
var moduleName = declaration.Key;
var parent = declarations.SingleOrDefault(item =>
ComponentTypes.Contains(item.DeclarationType) && item.ComponentName == moduleName);

Expand Down
17 changes: 7 additions & 10 deletions Rubberduck.Core/Navigation/CodeExplorer/CodeExplorerViewModel.cs
Expand Up @@ -19,17 +19,15 @@
using Rubberduck.UI.UnitTesting.Commands;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;

// ReSharper disable ExplicitCallerInfoArgument

namespace Rubberduck.Navigation.CodeExplorer
{
[Flags]
public enum CodeExplorerSortOrder
{
Undefined = 0,
Name = 1,
CodeLine = 1 << 2,
DeclarationType = 1 << 3,
CodeLine = 1 << 1,
DeclarationType = 1 << 2,
DeclarationTypeThenName = DeclarationType | Name,
DeclarationTypeThenCodeLine = DeclarationType | CodeLine
}
Expand Down Expand Up @@ -76,11 +74,11 @@ public sealed class CodeExplorerViewModel : ViewModelBase
RemoveCommand = new DelegateCommand(LogManager.GetCurrentClassLogger(), ExecuteRemoveCommand, _externalRemoveCommand.CanExecute);
}

OnPropertyChanged("Projects");
OnPropertyChanged(nameof(Projects));

SyncCodePaneCommand = syncProvider.GetSyncCommand(this);
// Force a call to EvaluateCanExecute
OnPropertyChanged("SyncCodePaneCommand");
OnPropertyChanged(nameof(SyncCodePaneCommand));
}

public ObservableCollection<ICodeExplorerNode> Projects { get; } = new ObservableCollection<ICodeExplorerNode>();
Expand Down Expand Up @@ -109,8 +107,8 @@ public ICodeExplorerNode SelectedItem

OnPropertyChanged();

OnPropertyChanged("ExportVisibility");
OnPropertyChanged("ExportAllVisibility");
OnPropertyChanged(nameof(ExportVisibility));
OnPropertyChanged(nameof(ExportAllVisibility));
}
}

Expand Down Expand Up @@ -266,9 +264,8 @@ private void Synchronize(List<Declaration> declarations)
foreach (var project in adding)
{
var model = new CodeExplorerProjectViewModel(project, declarations, _state, _vbe);
var model = new CodeExplorerProjectViewModel(project, declarations.Where(proj => proj.ProjectId.Equals(project.ProjectId)).ToList(), _state, _vbe);
Projects.Add(model);
//model.IsExpanded = true;
}
CanSearch = Projects.Any();
Expand Down
8 changes: 4 additions & 4 deletions Rubberduck.Core/Navigation/Folders/FolderExtensions.cs
Expand Up @@ -6,7 +6,7 @@ namespace Rubberduck.Navigation.Folders
{
public static class FolderExtensions
{
private const char FolderDelimiter = '.';
public const char FolderDelimiter = '.';

public static string RootFolder(this Declaration declaration)
{
Expand All @@ -17,12 +17,12 @@ public static string RootFolder(this Declaration declaration)

public static string SubFolderRoot(this string folder, string subfolder)
{
if (folder is null || subfolder is null || !subfolder.Trim('"').StartsWith(folder.Trim('"')))
if (folder is null || subfolder is null || !folder.Trim('"').StartsWith(subfolder.Trim('"')))
{
return string.Empty;
}

var subPath = subfolder.Trim('"').Substring(folder.Length - 1);
var subPath = folder.Trim('"').Substring(subfolder.Length + 1);
return subPath.Split(FolderDelimiter).FirstOrDefault() ?? string.Empty;
}

Expand Down Expand Up @@ -51,7 +51,7 @@ public static bool IsInSubFolder(this Declaration declaration, string folder)
return false;
}

return declarationPath.Take(declarationPath.Length).SequenceEqual(folderPath, StringComparer.Ordinal);
return declarationPath.Take(folderPath.Length).SequenceEqual(folderPath, StringComparer.Ordinal);
}

public static bool IsInFolderOrSubFolder(this Declaration declaration, string folder)
Expand Down
44 changes: 35 additions & 9 deletions Rubberduck.Core/UI/CodeExplorer/Commands/AddTemplateCommand.cs
@@ -1,3 +1,4 @@
using System;
using System.Collections.Generic;
using Rubberduck.Navigation.CodeExplorer;
using Rubberduck.Templates;
Expand Down Expand Up @@ -28,24 +29,49 @@ public bool CanExecuteForNode(ICodeExplorerNode model)

protected override bool EvaluateCanExecute(object parameter)
{
// TODO this cast needs to be safer.
var data = ((string templateName, CodeExplorerItemViewModel model)) parameter;
if (parameter is null)
{
return false;
}

try
{
// TODO this cast needs to be safer.
var data = ((string templateName, ICodeExplorerNode model))parameter;

return base.EvaluateCanExecute(data.model);
return base.EvaluateCanExecute(data.model);
}
catch (Exception ex)
{
Logger.Trace(ex);
return false;
}
}

protected override void OnExecute(object parameter)
{
// TODO this cast needs to be safer.
var data = ((string templateName, CodeExplorerItemViewModel model)) parameter;

if (string.IsNullOrWhiteSpace(data.templateName))
if (parameter is null)
{
return;
}

var moduleText = GetTemplate(data.templateName);
AddComponent(data.model, moduleText);
try
{
// TODO this cast needs to be safer.
var data = ((string templateName, ICodeExplorerNode node))parameter;

if (string.IsNullOrWhiteSpace(data.templateName) || !(data.node is CodeExplorerItemViewModel model))
{
return;
}

var moduleText = GetTemplate(data.templateName);
AddComponent(model, moduleText);
}
catch (Exception ex)
{
Logger.Trace(ex);
}
}

private string GetTemplate(string name)
Expand Down
Expand Up @@ -9,15 +9,15 @@ public class TemplateCommandParameterToTupleConverter : IMultiValueConverter
{
public object Convert(object[] values, Type targetType, object parameter, CultureInfo culture)
{
(string templateName, CodeExplorerItemViewModel model) data = (
(string templateName, ICodeExplorerNode model) data = (
values[0] as string,
values[1] as CodeExplorerItemViewModel);
values[1] as ICodeExplorerNode);
return data;
}

public object[] ConvertBack(object value, Type[] targetTypes, object parameter, CultureInfo culture)
{
var data = ((string templateName, CodeExplorerItemViewModel model))value;
var data = ((string templateName, ICodeExplorerNode model))value;
return new[] {(object) data.templateName, data.model};
}
}
Expand Down

0 comments on commit 64ae145

Please sign in to comment.