Skip to content

Commit b2f602f

Browse files
committed
Closes #3260
1 parent a243ad3 commit b2f602f

File tree

7 files changed

+356
-15
lines changed

7 files changed

+356
-15
lines changed

RetailCoder.VBE/Root/RubberduckModule.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -613,7 +613,8 @@ private IEnumerable<IMenuItem> GetFormDesignerContextMenuItems()
613613
{
614614
return new IMenuItem[]
615615
{
616-
KernelInstance.Get<FormDesignerRefactorRenameCommandMenuItem>()
616+
KernelInstance.Get<FormDesignerRefactorRenameCommandMenuItem>(),
617+
KernelInstance.Get<FormDesignerFindAllReferencesCommandMenuItem>()
617618
};
618619
}
619620

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -415,8 +415,10 @@
415415
<Compile Include="UI\CodeExplorer\Commands\AddStdModuleCommand.cs" />
416416
<Compile Include="UI\CodeExplorer\Commands\AddTestModuleCommand.cs" />
417417
<Compile Include="UI\CodeExplorer\Commands\AddComponentCommand.cs" />
418+
<Compile Include="UI\Command\FormDesignerFindAllReferencesCommand.cs" />
418419
<Compile Include="UI\Command\IndentCurrentProjectCommand.cs" />
419420
<Compile Include="UI\Command\MenuItems\CommandBars\ContextDescriptionLabelMenuItem.cs" />
421+
<Compile Include="UI\Command\MenuItems\FormDesignerFindAllReferencesCommandMenuItem.cs" />
420422
<Compile Include="UI\Command\MenuItems\IndentCurrentProjectCommandMenuItem.cs" />
421423
<Compile Include="UI\Command\MenuItems\ExportAllCommandMenuItem.cs" />
422424
<Compile Include="UI\Controls\EmptyUIRefresh.xaml.cs">

RetailCoder.VBE/UI/Command/FindAllReferencesCommand.cs

Lines changed: 48 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
using Rubberduck.Parsing.VBA;
88
using Rubberduck.UI.Command.MenuItems;
99
using Rubberduck.UI.Controls;
10+
using Rubberduck.VBEditor;
1011
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1112

1213
namespace Rubberduck.UI.Command
@@ -87,7 +88,8 @@ private void UpdateTab()
8788

8889
protected override bool EvaluateCanExecute(object parameter)
8990
{
90-
if (_vbe.ActiveCodePane == null || _state.Status != ParserState.Ready)
91+
if (_state.Status != ParserState.Ready ||
92+
(_vbe.ActiveCodePane == null && !(_vbe.SelectedVBComponent?.HasDesigner ?? false)))
9193
{
9294
return false;
9395
}
@@ -134,7 +136,7 @@ protected override void OnExecute(object parameter)
134136
}
135137
catch (Exception e)
136138
{
137-
Console.WriteLine(e);
139+
Logger.Error(e);
138140
}
139141
}
140142

@@ -160,9 +162,53 @@ private Declaration FindTarget(object parameter)
160162
return declaration;
161163
}
162164

165+
return _vbe.ActiveCodePane != null && (_vbe.SelectedVBComponent?.HasDesigner ?? false)
166+
? FindFormDesignerTarget()
167+
: FindCodePaneTarget();
168+
}
169+
170+
private Declaration FindCodePaneTarget()
171+
{
163172
return _state.FindSelectedDeclaration(_vbe.ActiveCodePane);
164173
}
165174

175+
private Declaration FindFormDesignerTarget(QualifiedModuleName? qualifiedModuleName = null)
176+
{
177+
var projectId = qualifiedModuleName.HasValue
178+
? qualifiedModuleName.Value.ProjectId
179+
: _vbe.ActiveVBProject.ProjectId;
180+
181+
var component = qualifiedModuleName.HasValue
182+
? qualifiedModuleName.Value.Component
183+
:_vbe.SelectedVBComponent;
184+
185+
186+
if (component?.HasDesigner ?? false)
187+
{
188+
if (qualifiedModuleName.HasValue)
189+
{
190+
return _state.DeclarationFinder.MatchName(qualifiedModuleName.Value.Name)
191+
.SingleOrDefault(m => m.ProjectId == projectId
192+
&& m.DeclarationType.HasFlag(qualifiedModuleName.Value.ComponentType)
193+
&& m.ComponentName == component.Name);
194+
}
195+
196+
var selectedCount = component.SelectedControls.Count;
197+
if (selectedCount > 1) { return null; }
198+
199+
// Cannot use DeclarationType.UserForm, parser only assigns UserForms the ClassModule flag
200+
var selectedType = selectedCount == 0 ? DeclarationType.ClassModule : DeclarationType.Control;
201+
string selectedName = selectedCount == 0 ? component.Name : component.SelectedControls[0].Name;
202+
203+
return _state.DeclarationFinder.MatchName(selectedName)
204+
.SingleOrDefault(m => m.ProjectId == projectId
205+
&& m.DeclarationType.HasFlag(selectedType)
206+
&& m.ComponentName == component.Name);
207+
}
208+
return null;
209+
}
210+
211+
166212
public void Dispose()
167213
{
168214
if (_state != null)
Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,32 @@
1+
using System.Runtime.InteropServices;
2+
using NLog;
3+
using Rubberduck.Parsing.VBA;
4+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
5+
6+
namespace Rubberduck.UI.Command
7+
{
8+
/// <summary>
9+
/// A command that locates all references to the active form designer component.
10+
/// </summary>
11+
[ComVisible(false)]
12+
public class FormDesignerFindAllReferencesCommand : CommandBase
13+
{
14+
private readonly FindAllReferencesCommand _findAllReferences;
15+
16+
public FormDesignerFindAllReferencesCommand(FindAllReferencesCommand findAllReferences)
17+
: base(LogManager.GetCurrentClassLogger())
18+
{
19+
_findAllReferences = findAllReferences;
20+
}
21+
22+
protected override bool EvaluateCanExecute(object parameter)
23+
{
24+
return _findAllReferences.CanExecute(parameter);
25+
}
26+
27+
protected override void OnExecute(object parameter)
28+
{
29+
_findAllReferences.Execute(parameter);
30+
}
31+
}
32+
}
Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
using Rubberduck.Parsing.VBA;
2+
using Rubberduck.UI.Command.MenuItems.ParentMenus;
3+
4+
namespace Rubberduck.UI.Command.MenuItems
5+
{
6+
public class FormDesignerFindAllReferencesCommandMenuItem : CommandMenuItemBase
7+
{
8+
public FormDesignerFindAllReferencesCommandMenuItem(CommandBase command)
9+
: base(command)
10+
{
11+
}
12+
13+
public override bool BeginGroup { get { return true; } }
14+
public override string Key { get { return "ContextMenu_FindAllReferences"; } }
15+
public override int DisplayOrder { get { return (int)NavigationMenuItemDisplayOrder.FindAllReferences; } }
16+
17+
public override bool EvaluateCanExecute(RubberduckParserState state)
18+
{
19+
return state != null && Command.CanExecute(null);
20+
}
21+
}
22+
}

RetailCoder.VBE/UI/SelectionChangeService.cs

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -109,25 +109,25 @@ private void DispatchSelectedDesignerDeclaration(IVBComponent component)
109109
return;
110110
}
111111

112-
var selected = component.SelectedControls.Count;
113-
if (selected == 1)
112+
var selectedCount = component.SelectedControls.Count;
113+
if (selectedCount == 1)
114114
{
115-
var name = component.SelectedControls.First().Name;
115+
var name = component.SelectedControls.Single().Name;
116116
var control =
117-
_parser.State.DeclarationFinder.UserDeclarations(DeclarationType.Control).SingleOrDefault(decl =>
118-
decl.IdentifierName.Equals(name) &&
119-
decl.ParentDeclaration.IdentifierName.Equals(component.Name) &&
120-
decl.ProjectId.Equals(component.ParentProject.ProjectId));
117+
_parser.State.DeclarationFinder.MatchName(name)
118+
.SingleOrDefault(d => d.DeclarationType == DeclarationType.Control
119+
&& d.ProjectId == component.ParentProject.ProjectId
120+
&& d.ParentDeclaration.IdentifierName == component.Name);
121121

122122
DispatchSelectedDeclaration(new DeclarationChangedEventArgs(null, control, component));
123123
return;
124124
}
125125
var form =
126-
_parser.State.DeclarationFinder.UserDeclarations(DeclarationType.UserForm).SingleOrDefault(decl =>
127-
decl.IdentifierName.Equals(component.Name) &&
128-
decl.ProjectId.Equals(component.ParentProject.ProjectId));
126+
_parser.State.DeclarationFinder.MatchName(component.Name)
127+
.SingleOrDefault(d => d.DeclarationType.HasFlag(DeclarationType.ClassModule)
128+
&& d.ProjectId == component.ParentProject.ProjectId);
129129

130-
DispatchSelectedDeclaration(new DeclarationChangedEventArgs(null, form, component, selected > 1));
130+
DispatchSelectedDeclaration(new DeclarationChangedEventArgs(null, form, component, selectedCount > 1));
131131
}
132132

133133
private void DispatchSelectedProjectNodeDeclaration(IVBComponent component)
@@ -166,7 +166,7 @@ private void DispatchSelectedProjectNodeDeclaration(IVBComponent component)
166166
private bool DeclarationChanged(Declaration current)
167167
{
168168
if ((_lastSelectedDeclaration == null && current == null) ||
169-
((_lastSelectedDeclaration != null && current != null) && !_lastSelectedDeclaration.Equals(current)))
169+
((_lastSelectedDeclaration != null && current != null) && _lastSelectedDeclaration.Equals(current)))
170170
{
171171
return false;
172172
}

0 commit comments

Comments
 (0)