Skip to content

Commit bd3d30f

Browse files
committed
Merge pull request #1435 from Hosch250/BugBlipper
Bug blipper
2 parents c8c3a96 + 8cad6e0 commit bd3d30f

File tree

57 files changed

+1095
-555
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

57 files changed

+1095
-555
lines changed

RetailCoder.VBE/Navigation/CodeExplorer/CodeExplorerCustomFolderViewModel.cs

Lines changed: 11 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ namespace Rubberduck.Navigation.CodeExplorer
1010
{
1111
public class CodeExplorerCustomFolderViewModel : CodeExplorerItemViewModel
1212
{
13+
private readonly string _fullPath;
1314
private readonly string _name;
1415
private readonly string _folderAttribute;
1516
private static readonly DeclarationType[] ComponentTypes =
@@ -20,25 +21,27 @@ public class CodeExplorerCustomFolderViewModel : CodeExplorerItemViewModel
2021
DeclarationType.UserForm,
2122
};
2223

23-
public CodeExplorerCustomFolderViewModel(string name, string fullPath, IEnumerable<Declaration> declarations)
24+
public CodeExplorerCustomFolderViewModel(string name, string fullPath)
2425
{
26+
_fullPath = fullPath;
2527
_name = name.Replace("\"", string.Empty);
2628
_folderAttribute = string.Format("@Folder(\"{0}\")", fullPath.Replace("\"", string.Empty));
2729

2830
_collapsedIcon = GetImageSource(resx.folder_horizontal);
2931
_expandedIcon = GetImageSource(resx.folder_horizontal_open);
32+
}
3033

31-
var items = declarations.ToList();
32-
33-
var parents = items.GroupBy(item => item.ComponentName).OrderBy(item => item.Key).ToList();
34+
public void AddNodes(List<Declaration> declarations)
35+
{
36+
var parents = declarations.GroupBy(item => item.ComponentName).OrderBy(item => item.Key).ToList();
3437
foreach (var component in parents)
3538
{
3639
try
3740
{
3841
var moduleName = component.Key;
39-
var parent = items.Single(item =>
42+
var parent = declarations.Single(item =>
4043
ComponentTypes.Contains(item.DeclarationType) && item.ComponentName == moduleName);
41-
var members = items.Where(item =>
44+
var members = declarations.Where(item =>
4245
!ComponentTypes.Contains(item.DeclarationType) && item.ComponentName == moduleName);
4346

4447
AddChild(new CodeExplorerComponentViewModel(parent, members));
@@ -52,6 +55,8 @@ public CodeExplorerCustomFolderViewModel(string name, string fullPath, IEnumerab
5255

5356
public string FolderAttribute { get { return _folderAttribute; } }
5457

58+
public string FullPath { get { return _fullPath; } }
59+
5560
public override string Name { get { return _name; } }
5661
public override string NameWithSignature { get { return Name; } }
5762

RetailCoder.VBE/Navigation/CodeExplorer/CodeExplorerProjectViewModel.cs

Lines changed: 30 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,9 @@
11
using System;
22
using System.Collections.Generic;
33
using System.Linq;
4-
using System.Text;
54
using System.Windows.Media.Imaging;
65
using Microsoft.Vbe.Interop;
6+
using Rubberduck.Navigation.Folders;
77
using Rubberduck.Parsing.Symbols;
88
using Rubberduck.VBEditor;
99
using resx = Rubberduck.UI.CodeExplorer.CodeExplorer;
@@ -14,6 +14,7 @@ public class CodeExplorerProjectViewModel : CodeExplorerItemViewModel
1414
{
1515
private readonly Declaration _declaration;
1616
public Declaration Declaration { get { return _declaration; } }
17+
private readonly CodeExplorerCustomFolderViewModel _folderTree;
1718

1819
private static readonly DeclarationType[] ComponentTypes =
1920
{
@@ -23,14 +24,16 @@ public class CodeExplorerProjectViewModel : CodeExplorerItemViewModel
2324
DeclarationType.UserForm,
2425
};
2526

26-
public CodeExplorerProjectViewModel(Declaration declaration, IEnumerable<Declaration> declarations)
27+
public CodeExplorerProjectViewModel(FolderHelper folderHelper, Declaration declaration, IEnumerable<Declaration> declarations)
2728
{
2829
_declaration = declaration;
2930
IsExpanded = true;
31+
_folderTree = folderHelper.GetFolderTree(declaration);
3032

3133
try
3234
{
33-
Items = FindFolders(declarations.ToList(), '.').ToList();
35+
FillFolders(declarations.ToList());
36+
Items = _folderTree.Items.ToList();
3437

3538
_icon = _declaration.Project.Protection == vbext_ProjectProtection.vbext_pp_locked
3639
? GetImageSource(resx.lock__exclamation)
@@ -42,44 +45,41 @@ public CodeExplorerProjectViewModel(Declaration declaration, IEnumerable<Declara
4245
}
4346
}
4447

45-
private static IEnumerable<CodeExplorerItemViewModel> FindFolders(IEnumerable<Declaration> declarations, char delimiter)
48+
private void FillFolders(IEnumerable<Declaration> declarations)
4649
{
47-
var root = new CodeExplorerCustomFolderViewModel(string.Empty, string.Empty, new List<Declaration>());
48-
4950
var items = declarations.ToList();
50-
var folders = items.Where(item => ComponentTypes.Contains(item.DeclarationType))
51+
var groupedItems = items.Where(item => ComponentTypes.Contains(item.DeclarationType))
5152
.GroupBy(item => item.CustomFolder)
5253
.OrderBy(item => item.Key);
53-
foreach (var grouping in folders)
54+
55+
foreach (var grouping in groupedItems)
5456
{
55-
CodeExplorerItemViewModel node = root;
56-
var parts = grouping.Key.Split(delimiter);
57-
var path = new StringBuilder();
58-
foreach (var part in parts)
57+
AddNodesToTree(_folderTree, items, grouping);
58+
}
59+
}
60+
61+
private bool AddNodesToTree(CodeExplorerCustomFolderViewModel tree, List<Declaration> items, IGrouping<string, Declaration> grouping)
62+
{
63+
foreach (var folder in tree.Items.OfType<CodeExplorerCustomFolderViewModel>())
64+
{
65+
if (grouping.Key.Replace("\"", string.Empty) != folder.FullPath)
5966
{
60-
if (path.Length != 0)
61-
{
62-
path.Append(delimiter);
63-
}
67+
continue;
68+
}
6469

65-
path.Append(part);
66-
var next = node.GetChild(part);
67-
if (next == null)
68-
{
69-
var currentPath = path.ToString();
70-
var parents = grouping.Where(item => ComponentTypes.Contains(item.DeclarationType) && item.CustomFolder == currentPath).ToList();
70+
var parents = grouping.Where(
71+
item => ComponentTypes.Contains(item.DeclarationType) &&
72+
item.CustomFolder.Replace("\"", string.Empty) == folder.FullPath)
73+
.ToList();
7174

72-
next = new CodeExplorerCustomFolderViewModel(part, currentPath, items.Where(item =>
73-
parents.Contains(item) || parents.Any(parent =>
74-
(item.ParentDeclaration != null && item.ParentDeclaration.Equals(parent)) || item.ComponentName == parent.ComponentName)));
75-
node.AddChild(next);
76-
}
75+
folder.AddNodes(items.Where(item => parents.Contains(item) || parents.Any(parent =>
76+
(item.ParentDeclaration != null && item.ParentDeclaration.Equals(parent)) ||
77+
item.ComponentName == parent.ComponentName)).ToList());
7778

78-
node = next;
79-
}
79+
return true;
8080
}
8181

82-
return root.Items;
82+
return tree.Items.OfType<CodeExplorerCustomFolderViewModel>().Any(node => AddNodesToTree(node, items, grouping));
8383
}
8484

8585
private readonly BitmapImage _icon;

RetailCoder.VBE/Navigation/CodeExplorer/CodeExplorerViewModel.cs

Lines changed: 19 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using System.Linq;
55
using System.Windows.Input;
66
using System.Windows.Threading;
7+
using Rubberduck.Navigation.Folders;
78
using Rubberduck.Parsing.Symbols;
89
using Rubberduck.Parsing.VBA;
910
using Rubberduck.UI;
@@ -14,16 +15,20 @@
1415

1516
namespace Rubberduck.Navigation.CodeExplorer
1617
{
17-
public class CodeExplorerViewModel : ViewModelBase
18+
public class CodeExplorerViewModel : ViewModelBase, IDisposable
1819
{
20+
private readonly FolderHelper _folderHelper;
1921
private readonly RubberduckParserState _state;
22+
private readonly List<ICommand> _commands;
2023
private readonly Dispatcher _dispatcher;
2124

22-
public CodeExplorerViewModel(RubberduckParserState state, List<ICommand> commands)
25+
public CodeExplorerViewModel(FolderHelper folderHelper, RubberduckParserState state, List<ICommand> commands)
2326
{
2427
_dispatcher = Dispatcher.CurrentDispatcher;
2528

29+
_folderHelper = folderHelper;
2630
_state = state;
31+
_commands = commands;
2732
_state.StateChanged += ParserState_StateChanged;
2833
_state.ModuleStateChanged += ParserState_ModuleStateChanged;
2934

@@ -198,7 +203,7 @@ private void ParserState_StateChanged(object sender, EventArgs e)
198203
}
199204

200205
var newProjects = new ObservableCollection<CodeExplorerItemViewModel>(userDeclarations.Select(grouping =>
201-
new CodeExplorerProjectViewModel(
206+
new CodeExplorerProjectViewModel(_folderHelper,
202207
grouping.SingleOrDefault(declaration => declaration.DeclarationType == DeclarationType.Project),
203208
grouping)));
204209

@@ -357,5 +362,16 @@ private void ExecuteRemoveComand(object param)
357362

358363
_externalRemoveCommand.Execute(param);
359364
}
365+
366+
public void Dispose()
367+
{
368+
foreach (var command in _commands)
369+
{
370+
if (command is IDisposable)
371+
{
372+
((IDisposable) command).Dispose();
373+
}
374+
}
375+
}
360376
}
361377
}
Lines changed: 72 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,72 @@
1+
using System.Linq;
2+
using Rubberduck.Navigation.CodeExplorer;
3+
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.Settings;
6+
7+
namespace Rubberduck.Navigation.Folders
8+
{
9+
public class FolderHelper
10+
{
11+
private readonly RubberduckParserState _state;
12+
private readonly ConfigurationLoader _configLoader;
13+
14+
private static readonly DeclarationType[] ComponentTypes =
15+
{
16+
DeclarationType.ClassModule,
17+
DeclarationType.Document,
18+
DeclarationType.ProceduralModule,
19+
DeclarationType.UserForm,
20+
};
21+
22+
public FolderHelper(RubberduckParserState state, ConfigurationLoader configLoader)
23+
{
24+
_state = state;
25+
_configLoader = configLoader;
26+
}
27+
28+
public CodeExplorerCustomFolderViewModel GetFolderTree(Declaration declaration = null)
29+
{
30+
var delimiter = GetDelimiter();
31+
32+
var root = new CodeExplorerCustomFolderViewModel(string.Empty, string.Empty);
33+
34+
var items = declaration == null
35+
? _state.AllUserDeclarations.ToList()
36+
: _state.AllUserDeclarations.Where(d => d.ProjectId == declaration.ProjectId).ToList();
37+
38+
var folders = items.Where(item => ComponentTypes.Contains(item.DeclarationType))
39+
.Select(item => item.CustomFolder.Replace("\"", string.Empty))
40+
.Distinct()
41+
.Select(item => item.Split(delimiter));
42+
43+
foreach (var folder in folders)
44+
{
45+
var currentNode = root;
46+
var fullPath = string.Empty;
47+
48+
foreach (var section in folder)
49+
{
50+
fullPath += string.IsNullOrEmpty(fullPath) ? section : delimiter + section;
51+
52+
var node = currentNode.Items.FirstOrDefault(i => i.Name == section);
53+
if (node == null)
54+
{
55+
node = new CodeExplorerCustomFolderViewModel(section, fullPath);
56+
currentNode.AddChild(node);
57+
}
58+
59+
currentNode = (CodeExplorerCustomFolderViewModel)node;
60+
}
61+
}
62+
63+
return root;
64+
}
65+
66+
private char GetDelimiter()
67+
{
68+
var settings = _configLoader.LoadConfiguration();
69+
return settings.UserSettings.GeneralSettings.Delimiter;
70+
}
71+
}
72+
}

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -365,6 +365,7 @@
365365
<Compile Include="Inspections\ObjectVariableNotSetInspection.cs" />
366366
<Compile Include="Inspections\RemoveExplicitCallStatmentQuickFix.cs" />
367367
<Compile Include="Navigation\CodeExplorer\CodeExplorerErrorNodeViewModel.cs" />
368+
<Compile Include="Navigation\Folders\FolderHelper.cs" />
368369
<Compile Include="Settings\RubberduckHotkey.cs" />
369370
<Compile Include="UI\About\AboutControl.xaml.cs">
370371
<DependentUpon>AboutControl.xaml</DependentUpon>
@@ -659,10 +660,12 @@
659660
<DesignTime>True</DesignTime>
660661
<DependentUpon>RubberduckUI.sv.resx</DependentUpon>
661662
</Compile>
663+
<Compile Include="UI\Settings\Converters\AssertModeValueToTextConverter.cs" />
664+
<Compile Include="UI\Settings\Converters\DelimiterToTextConverter.cs" />
662665
<Compile Include="UI\Settings\Converters\EndOfLineCommentStyleToTextConverter.cs" />
663666
<Compile Include="UI\Settings\Converters\EndOfLineCommentStyleValueTextToEnumValueConverter.cs" />
664667
<Compile Include="UI\Settings\Converters\AssertModeToTextConverter.cs" />
665-
<Compile Include="UI\Settings\Converters\AssertModeValueToTextConverter.cs" />
668+
<Compile Include="UI\Settings\Converters\DelimiterValueToTextConverter.cs" />
666669
<Compile Include="UI\Settings\Converters\BindingModeValueToTextConverter.cs" />
667670
<Compile Include="UI\Settings\Converters\BindingModeToTextConverter.cs" />
668671
<Compile Include="UI\Settings\Converters\EndOfLineCommentStyleToVisibilityConverter.cs" />

RetailCoder.VBE/Settings/ConfigurationLoader.cs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -57,6 +57,12 @@ public override Configuration LoadConfiguration()
5757
AssociateHotkeyCommands(config);
5858
}
5959

60+
// 0 is the default, and parses just fine into a `char`. We require '.' or '/'.
61+
if (!new[] {',', '/'}.Contains(config.UserSettings.GeneralSettings.Delimiter))
62+
{
63+
config.UserSettings.GeneralSettings.Delimiter = '.';
64+
}
65+
6066
if (config.UserSettings.ToDoListSettings == null)
6167
{
6268
config.UserSettings.ToDoListSettings = new ToDoListSettings(GetDefaultTodoMarkers());
@@ -195,7 +201,7 @@ private GeneralSettings GetDefaultGeneralSettings()
195201
new HotkeySetting{Name=RubberduckHotkey.RefactorRename.ToString(), IsEnabled=true, HasCtrlModifier = true, HasShiftModifier = true, Key1="R", Command = commandMappings[RubberduckHotkey.RefactorRename]},
196202
new HotkeySetting{Name=RubberduckHotkey.RefactorExtractMethod.ToString(), IsEnabled=true, HasCtrlModifier = true, HasShiftModifier = true, Key1="M", Command = commandMappings[RubberduckHotkey.RefactorExtractMethod]}
197203
},
198-
false, 10);
204+
false, 10, '.');
199205
}
200206

201207
public ToDoMarker[] GetDefaultTodoMarkers()

RetailCoder.VBE/Settings/GeneralSettings.cs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ interface IGeneralSettings
88
HotkeySetting[] HotkeySettings { get; set; }
99
bool AutoSaveEnabled { get; set; }
1010
int AutoSavePeriod { get; set; }
11+
char Delimiter { get; set; }
1112
}
1213

1314
[XmlType(AnonymousType = true)]
@@ -21,17 +22,20 @@ public class GeneralSettings : IGeneralSettings
2122
public bool AutoSaveEnabled { get; set; }
2223
public int AutoSavePeriod { get; set; }
2324

25+
public char Delimiter { get; set; }
26+
2427
public GeneralSettings()
2528
{
2629
//empty constructor needed for serialization
2730
}
2831

29-
public GeneralSettings(DisplayLanguageSetting language, HotkeySetting[] hotkeySettings, bool autoSaveEnabled, int autoSavePeriod)
32+
public GeneralSettings(DisplayLanguageSetting language, HotkeySetting[] hotkeySettings, bool autoSaveEnabled, int autoSavePeriod, char delimiter)
3033
{
3134
Language = language;
3235
HotkeySettings = hotkeySettings;
3336
AutoSaveEnabled = autoSaveEnabled;
3437
AutoSavePeriod = autoSavePeriod;
38+
Delimiter = '.';
3539
}
3640
}
3741
}

RetailCoder.VBE/UI/CodeExplorer/Commands/CodeExplorer_ExportCommand.cs

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
using System;
12
using System.Collections.Generic;
23
using System.Linq;
34
using System.Windows.Forms;
@@ -7,7 +8,7 @@
78

89
namespace Rubberduck.UI.CodeExplorer.Commands
910
{
10-
public class CodeExplorer_ExportCommand : CommandBase
11+
public class CodeExplorer_ExportCommand : CommandBase, IDisposable
1112
{
1213
private readonly ISaveFileDialog _saveFileDialog;
1314
private readonly Dictionary<vbext_ComponentType, string> _exportableFileExtensions = new Dictionary<vbext_ComponentType, string>
@@ -52,5 +53,13 @@ public override void Execute(object parameter)
5253
component.Export(_saveFileDialog.FileName);
5354
}
5455
}
56+
57+
public void Dispose()
58+
{
59+
if (_saveFileDialog != null)
60+
{
61+
_saveFileDialog.Dispose();
62+
}
63+
}
5564
}
5665
}

0 commit comments

Comments
 (0)