Skip to content

Commit 98b9f4a

Browse files
committed
Fix EvaluateCanExecute for find all implementations, closes #3045
1 parent 7baf5fb commit 98b9f4a

File tree

7 files changed

+285
-205
lines changed

7 files changed

+285
-205
lines changed

Rubberduck.Core/Navigation/CodeExplorer/CodeExplorerViewModel.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -681,7 +681,7 @@ public double? FontSize
681681
public RenameCommand RenameCommand { get; set; }
682682
public IndentCommand IndenterCommand { get; set; }
683683
public CodeExplorerFindAllReferencesCommand FindAllReferencesCommand { get; set; }
684-
public FindAllImplementationsCommand FindAllImplementationsCommand { get; set; }
684+
public CodeExplorerFindAllImplementationsCommand FindAllImplementationsCommand { get; set; }
685685
public CommandBase CollapseAllSubnodesCommand { get; }
686686
public CopyResultsCommand CopyResultsCommand { get; set; }
687687
public CommandBase ExpandAllSubnodesCommand { get; }
Lines changed: 48 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,48 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using Rubberduck.Navigation.CodeExplorer;
4+
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.UI.Controls;
6+
7+
namespace Rubberduck.UI.CodeExplorer.Commands
8+
{
9+
public class CodeExplorerFindAllImplementationsCommand : CodeExplorerCommandBase
10+
{
11+
private static readonly Type[] ApplicableNodes =
12+
{
13+
typeof(CodeExplorerComponentViewModel),
14+
typeof(CodeExplorerMemberViewModel)
15+
};
16+
17+
private readonly RubberduckParserState _state;
18+
private readonly FindAllImplementationsService _finder;
19+
20+
public CodeExplorerFindAllImplementationsCommand(RubberduckParserState state, FindAllImplementationsService finder)
21+
{
22+
_state = state;
23+
_finder = finder;
24+
}
25+
26+
protected override void OnExecute(object parameter)
27+
{
28+
if (_state.Status != ParserState.Ready ||
29+
!(parameter is CodeExplorerItemViewModel node) ||
30+
node.Declaration == null)
31+
{
32+
return;
33+
}
34+
35+
_finder.FindAllImplementations(node.Declaration);
36+
}
37+
38+
public override IEnumerable<Type> ApplicableNodeTypes => ApplicableNodes;
39+
40+
protected override bool EvaluateCanExecute(object parameter)
41+
{
42+
return base.EvaluateCanExecute(parameter) &&
43+
_state.Status == ParserState.Ready &&
44+
parameter is CodeExplorerItemViewModel node &&
45+
_finder.CanFind(node.Declaration);
46+
}
47+
}
48+
}
Lines changed: 10 additions & 173 deletions
Original file line numberDiff line numberDiff line change
@@ -1,16 +1,8 @@
1-
using System;
2-
using System.Collections.Generic;
3-
using System.Linq;
41
using System.Runtime.InteropServices;
52
using NLog;
6-
using Rubberduck.Interaction;
7-
using Rubberduck.Interaction.Navigation;
83
using Rubberduck.Parsing.Symbols;
9-
using Rubberduck.Parsing.UIContext;
104
using Rubberduck.Parsing.VBA;
11-
using Rubberduck.Resources;
125
using Rubberduck.UI.Controls;
13-
using Rubberduck.VBEditor;
146
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
157

168
namespace Rubberduck.UI.Command
@@ -19,100 +11,36 @@ namespace Rubberduck.UI.Command
1911
/// A command that finds all implementations of a specified method, or of the active interface module.
2012
/// </summary>
2113
[ComVisible(false)]
22-
public class FindAllImplementationsCommand : CommandBase, IDisposable
14+
public class FindAllImplementationsCommand : CommandBase
2315
{
24-
private readonly INavigateCommand _navigateCommand;
25-
private readonly IMessageBox _messageBox;
2616
private readonly RubberduckParserState _state;
27-
private readonly ISearchResultsWindowViewModel _viewModel;
28-
private readonly SearchResultPresenterInstanceManager _presenterService;
2917
private readonly IVBE _vbe;
30-
private readonly IUiDispatcher _uiDispatcher;
18+
private readonly FindAllImplementationsService _finder;
3119

32-
private new static readonly Logger Logger = LogManager.GetCurrentClassLogger();
33-
34-
public FindAllImplementationsCommand(INavigateCommand navigateCommand, IMessageBox messageBox,
35-
RubberduckParserState state, IVBE vbe, ISearchResultsWindowViewModel viewModel,
36-
SearchResultPresenterInstanceManager presenterService, IUiDispatcher uiDispatcher)
20+
public FindAllImplementationsCommand(RubberduckParserState state, IVBE vbe, ISearchResultsWindowViewModel viewModel, FindAllImplementationsService finder)
3721
: base(LogManager.GetCurrentClassLogger())
3822
{
39-
_navigateCommand = navigateCommand;
40-
_messageBox = messageBox;
23+
_finder = finder;
4124
_state = state;
4225
_vbe = vbe;
43-
_viewModel = viewModel;
44-
_presenterService = presenterService;
45-
_uiDispatcher = uiDispatcher;
46-
47-
_state.StateChanged += _state_StateChanged;
48-
}
49-
50-
private Declaration FindNewDeclaration(Declaration declaration)
51-
{
52-
return _state.AllUserDeclarations.SingleOrDefault(item =>
53-
item.ProjectId == declaration.ProjectId &&
54-
item.ComponentName == declaration.ComponentName &&
55-
item.ParentScope == declaration.ParentScope &&
56-
item.IdentifierName == declaration.IdentifierName &&
57-
item.DeclarationType == declaration.DeclarationType);
5826
}
5927

60-
private void _state_StateChanged(object sender, ParserStateEventArgs e)
61-
{
62-
if (e.State != ParserState.Ready) { return; }
63-
64-
if (_viewModel == null) { return; }
65-
66-
_uiDispatcher.InvokeAsync(UpdateTab);
67-
}
68-
69-
private void UpdateTab()
28+
protected override bool EvaluateCanExecute(object parameter)
7029
{
71-
try
72-
{
73-
var findImplementationsTabs = _viewModel.Tabs.Where(
74-
t => t.Header.StartsWith(RubberduckUI.AllImplementations_Caption.Replace("'{0}'", ""))).ToList();
75-
76-
foreach (var tab in findImplementationsTabs)
77-
{
78-
var newTarget = FindNewDeclaration(tab.Target);
79-
if (newTarget == null)
80-
{
81-
tab.CloseCommand.Execute(null);
82-
return;
83-
}
84-
85-
var vm = CreateViewModel(newTarget);
86-
if (vm.SearchResults.Any())
87-
{
88-
tab.SearchResults = vm.SearchResults;
89-
tab.Target = vm.Target;
90-
}
91-
else
92-
{
93-
tab.CloseCommand.Execute(null);
94-
}
95-
}
96-
}
97-
catch (Exception exception)
30+
if (_state.Status != ParserState.Ready)
9831
{
99-
Logger.Error(exception, "Exception thrown while trying to update the find implementations tab.");
32+
return false;
10033
}
101-
}
10234

103-
protected override bool EvaluateCanExecute(object parameter)
104-
{
10535
using (var codePane = _vbe.ActiveCodePane)
10636
{
107-
if (codePane == null || codePane.IsWrappingNullReference || _state.Status != ParserState.Ready)
37+
if (codePane == null || codePane.IsWrappingNullReference)
10838
{
10939
return false;
11040
}
11141

11242
var target = FindTarget(parameter);
113-
var canExecute = target != null;
114-
115-
return canExecute;
43+
return _finder.CanFind(target);
11644
}
11745
}
11846

@@ -129,77 +57,7 @@ protected override void OnExecute(object parameter)
12957
return;
13058
}
13159

132-
var viewModel = CreateViewModel(declaration);
133-
if (!viewModel.SearchResults.Any())
134-
{
135-
_messageBox.NotifyWarn(string.Format(RubberduckUI.AllReferences_NoneFound, declaration.IdentifierName), RubberduckUI.Rubberduck);
136-
return;
137-
}
138-
139-
if (viewModel.SearchResults.Count == 1)
140-
{
141-
_navigateCommand.Execute(viewModel.SearchResults.Single().GetNavigationArgs());
142-
return;
143-
}
144-
145-
_viewModel.AddTab(viewModel);
146-
_viewModel.SelectedTab = viewModel;
147-
148-
try
149-
{
150-
var presenter = _presenterService.Presenter(_viewModel);
151-
presenter.Show();
152-
}
153-
catch (Exception e)
154-
{
155-
Console.WriteLine(e);
156-
}
157-
}
158-
159-
private SearchResultsViewModel CreateViewModel(Declaration target)
160-
{
161-
IEnumerable<Declaration> implementations;
162-
if (target is ClassModuleDeclaration classModule)
163-
{
164-
implementations = _state.DeclarationFinder.FindAllImplementationsOfInterface(classModule);
165-
}
166-
else if (target is IInterfaceExposable member && member.IsInterfaceMember)
167-
{
168-
implementations = _state.DeclarationFinder.FindInterfaceImplementationMembers(target);
169-
}
170-
else
171-
{
172-
implementations = target is ModuleBodyElementDeclaration implementation
173-
? _state.DeclarationFinder.FindInterfaceImplementationMembers(implementation.InterfaceMemberImplemented)
174-
: Enumerable.Empty<Declaration>();
175-
}
176-
177-
var results = implementations.Select(declaration =>
178-
new SearchResultItem(
179-
declaration.ParentScopeDeclaration,
180-
new NavigateCodeEventArgs(declaration.QualifiedName.QualifiedModuleName, declaration.Selection),
181-
GetModuleLine(declaration.QualifiedName.QualifiedModuleName, declaration.Selection.StartLine)));
182-
183-
var accessor = target.DeclarationType.HasFlag(DeclarationType.PropertyGet) ? "(get)"
184-
: target.DeclarationType.HasFlag(DeclarationType.PropertyLet) ? "(let)"
185-
: target.DeclarationType.HasFlag(DeclarationType.PropertySet) ? "(set)"
186-
: string.Empty;
187-
188-
var tabCaption = $"{target.IdentifierName} {accessor}".Trim();
189-
190-
var viewModel = new SearchResultsViewModel(_navigateCommand,
191-
string.Format(RubberduckUI.SearchResults_AllImplementationsTabFormat, tabCaption), target, results);
192-
193-
return viewModel;
194-
}
195-
196-
private string GetModuleLine(QualifiedModuleName module, int line)
197-
{
198-
var component = _state.ProjectsProvider.Component(module);
199-
using (var codeModule = component.CodeModule)
200-
{
201-
return codeModule.GetLines(line, 1).Trim();
202-
}
60+
_finder.FindAllImplementations(declaration);
20361
}
20462

20563
private Declaration FindTarget(object parameter)
@@ -214,26 +72,5 @@ private Declaration FindTarget(object parameter)
21472
return _state.FindSelectedDeclaration(activePane);
21573
}
21674
}
217-
218-
public void Dispose()
219-
{
220-
Dispose(true);
221-
GC.SuppressFinalize(this);
222-
}
223-
224-
private bool _isDisposed;
225-
protected virtual void Dispose(bool disposing)
226-
{
227-
if (_isDisposed || !disposing)
228-
{
229-
return;
230-
}
231-
232-
if (_state != null)
233-
{
234-
_state.StateChanged -= _state_StateChanged;
235-
}
236-
_isDisposed = true;
237-
}
23875
}
23976
}

Rubberduck.Core/UI/Command/FindAllReferencesCommand.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ public class FindAllReferencesCommand : CommandBase
1717
{
1818
private readonly RubberduckParserState _state;
1919
private readonly IVBE _vbe;
20-
private FindAllReferencesService _finder;
20+
private readonly FindAllReferencesService _finder;
2121

2222
public FindAllReferencesCommand(RubberduckParserState state, IVBE vbe, ISearchResultsWindowViewModel viewModel, FindAllReferencesService finder)
2323
: base(LogManager.GetCurrentClassLogger())

0 commit comments

Comments
 (0)