Skip to content

Commit 70f513d

Browse files
authored
Merge pull request #4240 from comintern/experimental
Subclass All the Things! - Event rework to more reliably attach to windows.
2 parents 1cf6e0f + aa8770e commit 70f513d

Some content is hidden

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

54 files changed

+1112
-408
lines changed

Rubberduck.Core/UI/Command/MenuItems/CommandBars/RubberduckCommandBar.cs

Lines changed: 4 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -57,14 +57,11 @@ private void EvaluateCanExecute(RubberduckParserState state, Declaration selecte
5757

5858
private void OnSelectionChange(object sender, DeclarationChangedEventArgs e)
5959
{
60-
var caption = e.ActivePane != null
61-
? _formatter.Format(e.ActivePane, e.Declaration)
62-
: _formatter.Format(e.Declaration, e.MultipleControlsSelected);
63-
64-
if (string.IsNullOrEmpty(caption) && e.VBComponent != null)
60+
var caption = _formatter.Format(e.Declaration, e.MultipleControlsSelected);
61+
if (string.IsNullOrEmpty(caption))
6562
{
66-
//Fallback caption for selections in the Project window.
67-
caption = $"{e.VBComponent.ParentProject.Name}.{e.VBComponent.Name} ({e.VBComponent.Type})";
63+
//Fallback caption for selections in the Project window.
64+
caption = e.FallbackCaption;
6865
}
6966

7067
var refCount = e.Declaration?.References.Count() ?? 0;

Rubberduck.Core/UI/SelectionChangeService.cs

Lines changed: 99 additions & 74 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66
using Rubberduck.VBEditor.Events;
77
using Rubberduck.VBEditor.SafeComWrappers;
88
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
9+
using Rubberduck.VBEditor.WindowsApi;
910

1011
namespace Rubberduck.UI
1112
{
@@ -33,47 +34,60 @@ public SelectionChangeService(IVBE vbe, IParseCoordinator parser)
3334
VBENativeServices.WindowFocusChange += OnVbeFocusChanged;
3435
}
3536

36-
private void OnVbeSelectionChanged(object sender, SelectionChangedEventArgs e)
37+
private void OnVbeSelectionChanged(object sender, EventArgs e)
3738
{
38-
if (e.CodePane == null || e.CodePane.IsWrappingNullReference)
39+
Task.Run(() =>
3940
{
40-
return;
41-
}
42-
43-
new Task(() =>
44-
{
45-
var eventArgs = new DeclarationChangedEventArgs(e.CodePane, _parser.State.FindSelectedDeclaration(e.CodePane));
46-
DispatchSelectedDeclaration(eventArgs);
47-
}).Start();
41+
using (var active = _vbe.ActiveCodePane)
42+
{
43+
if (active == null)
44+
{
45+
return;
46+
}
47+
var eventArgs = new DeclarationChangedEventArgs(_vbe, _parser.State.FindSelectedDeclaration(active));
48+
DispatchSelectedDeclaration(eventArgs);
49+
}
50+
});
4851
}
4952

5053
private void OnVbeFocusChanged(object sender, WindowChangedEventArgs e)
5154
{
5255
if (e.EventType == FocusType.GotFocus)
5356
{
54-
switch (e.Window.Type)
57+
switch (e.Hwnd.ToWindowType())
5558
{
56-
case WindowKind.Designer:
57-
//Designer or control on designer form selected.
58-
if (e.Window == null || e.Window.IsWrappingNullReference || e.Window.Type != WindowKind.Designer)
59+
case WindowType.DesignerWindow:
60+
Task.Run(() =>
5961
{
60-
return;
61-
}
62-
new Task(() => DispatchSelectedDesignerDeclaration(_vbe.SelectedVBComponent)).Start();
62+
using (var component = _vbe.SelectedVBComponent)
63+
{
64+
DispatchSelectedDesignerDeclaration(component);
65+
}
66+
});
6367
break;
64-
case WindowKind.CodeWindow:
68+
case WindowType.CodePane:
6569
//Caret changed in a code pane.
66-
if (e.CodePane != null && !e.CodePane.IsWrappingNullReference)
70+
Task.Run(() =>
6771
{
68-
new Task(() => DispatchSelectedDeclaration(new DeclarationChangedEventArgs(e.CodePane, _parser.State.FindSelectedDeclaration(e.CodePane)))).Start();
69-
}
72+
using (var pane = VBENativeServices.GetCodePaneFromHwnd(e.Hwnd))
73+
{
74+
DispatchSelectedDeclaration(
75+
new DeclarationChangedEventArgs(_vbe, _parser.State.FindSelectedDeclaration(pane)));
76+
}
77+
});
7078
break;
7179
}
7280
}
7381
else if (e.EventType == FocusType.ChildFocus)
7482
{
7583
//Treeview selection changed in project window.
76-
new Task(() => DispatchSelectedProjectNodeDeclaration(_vbe.SelectedVBComponent)).Start();
84+
Task.Run(() =>
85+
{
86+
using (var component = _vbe.SelectedVBComponent)
87+
{
88+
DispatchSelectedProjectNodeDeclaration(component);
89+
}
90+
});
7791
}
7892
}
7993

@@ -103,25 +117,29 @@ private void DispatchSelectedDesignerDeclaration(IVBComponent component)
103117
return;
104118
}
105119

106-
var selectedCount = component.SelectedControls.Count;
107-
if (selectedCount == 1)
120+
using (var selected = component.SelectedControls)
121+
using (var parent = component.ParentProject)
108122
{
109-
var name = component.SelectedControls.Single().Name;
110-
var control =
111-
_parser.State.DeclarationFinder.MatchName(name)
112-
.SingleOrDefault(d => d.DeclarationType == DeclarationType.Control
113-
&& d.ProjectId == component.ParentProject.ProjectId
114-
&& d.ParentDeclaration.IdentifierName == component.Name);
115-
116-
DispatchSelectedDeclaration(new DeclarationChangedEventArgs(null, control, component));
117-
return;
118-
}
119-
var form =
120-
_parser.State.DeclarationFinder.MatchName(component.Name)
121-
.SingleOrDefault(d => d.DeclarationType.HasFlag(DeclarationType.ClassModule)
122-
&& d.ProjectId == component.ParentProject.ProjectId);
123+
var selectedCount = selected.Count;
124+
if (selectedCount == 1)
125+
{
126+
var name = selected.Single().Name;
127+
var control =
128+
_parser.State.DeclarationFinder.MatchName(name)
129+
.SingleOrDefault(d => d.DeclarationType == DeclarationType.Control
130+
&& d.ProjectId == parent.ProjectId
131+
&& d.ParentDeclaration.IdentifierName == component.Name);
132+
133+
DispatchSelectedDeclaration(new DeclarationChangedEventArgs(_vbe, control));
134+
return;
135+
}
136+
var form =
137+
_parser.State.DeclarationFinder.MatchName(component.Name)
138+
.SingleOrDefault(d => d.DeclarationType.HasFlag(DeclarationType.ClassModule)
139+
&& d.ProjectId == parent.ProjectId);
123140

124-
DispatchSelectedDeclaration(new DeclarationChangedEventArgs(null, form, component, selectedCount > 1));
141+
DispatchSelectedDeclaration(new DeclarationChangedEventArgs(_vbe, form, selectedCount > 1));
142+
}
125143
}
126144

127145
private void DispatchSelectedProjectNodeDeclaration(IVBComponent component)
@@ -131,40 +149,39 @@ private void DispatchSelectedProjectNodeDeclaration(IVBComponent component)
131149
return;
132150
}
133151

134-
if ((component == null || component.IsWrappingNullReference) && !_vbe.ActiveVBProject.IsWrappingNullReference)
152+
using (var active = _vbe.ActiveVBProject)
135153
{
136-
//The user might have selected the project node in Project Explorer. If they've chosen a folder, we'll return the project anyway.
137-
var project =
138-
_parser.State.DeclarationFinder.UserDeclarations(DeclarationType.Project)
139-
.SingleOrDefault(decl => decl.ProjectId.Equals(_vbe.ActiveVBProject.ProjectId));
154+
if ((component == null || component.IsWrappingNullReference) && !active.IsWrappingNullReference)
155+
{
156+
//The user might have selected the project node in Project Explorer. If they've chosen a folder, we'll return the project anyway.
157+
var project =
158+
_parser.State.DeclarationFinder.UserDeclarations(DeclarationType.Project)
159+
.SingleOrDefault(decl => decl.ProjectId.Equals(active.ProjectId));
140160

141-
DispatchSelectedDeclaration(new DeclarationChangedEventArgs(null, project, component));
142-
}
143-
else if (component != null && component.Type == ComponentType.UserForm && component.HasOpenDesigner)
144-
{
145-
DispatchSelectedDesignerDeclaration(component);
146-
}
147-
else if (component != null)
148-
{
149-
150-
var module =
151-
_parser.State.AllUserDeclarations.SingleOrDefault(
152-
decl => decl.DeclarationType.HasFlag(DeclarationType.Module) &&
153-
decl.IdentifierName.Equals(component.Name) &&
154-
decl.ProjectId.Equals(_vbe.ActiveVBProject.ProjectId));
155-
156-
DispatchSelectedDeclaration(new DeclarationChangedEventArgs(null, module, component));
161+
DispatchSelectedDeclaration(new DeclarationChangedEventArgs(_vbe, project));
162+
}
163+
else if (component != null && component.Type == ComponentType.UserForm && component.HasOpenDesigner)
164+
{
165+
DispatchSelectedDesignerDeclaration(component);
166+
}
167+
else if (component != null)
168+
{
169+
170+
var module =
171+
_parser.State.AllUserDeclarations.SingleOrDefault(
172+
decl => decl.DeclarationType.HasFlag(DeclarationType.Module) &&
173+
decl.IdentifierName.Equals(component.Name) &&
174+
decl.ProjectId.Equals(active.ProjectId));
175+
176+
DispatchSelectedDeclaration(new DeclarationChangedEventArgs(_vbe, module));
177+
}
157178
}
158179
}
159180

160181
private bool DeclarationChanged(Declaration current)
161182
{
162-
if ((_lastSelectedDeclaration == null && current == null) ||
163-
((_lastSelectedDeclaration != null && current != null) && _lastSelectedDeclaration.Equals(current)))
164-
{
165-
return false;
166-
}
167-
return true;
183+
return (_lastSelectedDeclaration != null || current != null) &&
184+
(_lastSelectedDeclaration == null || current == null || !_lastSelectedDeclaration.Equals(current));
168185
}
169186

170187
public void Dispose()
@@ -176,18 +193,26 @@ public void Dispose()
176193

177194
public class DeclarationChangedEventArgs : EventArgs
178195
{
179-
public ICodePane ActivePane { get; private set; }
180-
public Declaration Declaration { get; private set; }
181-
// ReSharper disable once InconsistentNaming
182-
public IVBComponent VBComponent { get; private set; }
183-
public bool MultipleControlsSelected { get; private set; }
196+
public Declaration Declaration { get; }
197+
public string FallbackCaption { get; }
198+
public bool MultipleControlsSelected { get; }
184199

185-
public DeclarationChangedEventArgs(ICodePane pane, Declaration declaration, IVBComponent component = null, bool multipleControls = false)
200+
public DeclarationChangedEventArgs(IVBE vbe, Declaration declaration, bool multipleControls = false)
186201
{
187-
ActivePane = pane;
188202
Declaration = declaration;
189-
VBComponent = component;
190203
MultipleControlsSelected = multipleControls;
204+
if (Declaration != null && !string.IsNullOrEmpty(Declaration.QualifiedName.MemberName))
205+
{
206+
return;
207+
}
208+
209+
using (var active = vbe.SelectedVBComponent)
210+
using (var parent = active?.ParentProject)
211+
{
212+
FallbackCaption =
213+
$"{parent?.Name ?? string.Empty}.{active?.Name ?? string.Empty} ({active?.Type.ToString() ?? string.Empty})"
214+
.Trim('.');
215+
}
191216
}
192217
}
193218
}

Rubberduck.Main/ComClientLibrary/UI/DockableWindowHost.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@
1010
using NLog;
1111
using Rubberduck.Resources.Registration;
1212
using Rubberduck.UI.CustomComWrappers;
13+
using Rubberduck.VBEditor.Events;
1314

1415
namespace Rubberduck.UI
1516
{

Rubberduck.Parsing/ComReflection/ReferencedDeclarationsCollector.cs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -177,6 +177,7 @@ public List<Declaration> LoadDeclarationsFromLibrary()
177177
var enumTree = new SerializableDeclarationTree(enumDeclaration);
178178
moduleTree.AddChildTree(enumTree);
179179
enumTree.AddChildren(members);
180+
continue;
180181
}
181182

182183
var structure = module as ComStruct;
@@ -190,6 +191,7 @@ public List<Declaration> LoadDeclarationsFromLibrary()
190191
var typeTree = new SerializableDeclarationTree(typeDeclaration);
191192
moduleTree.AddChildTree(typeTree);
192193
typeTree.AddChildren(members);
194+
continue;
193195
}
194196

195197
var fields = module as IComTypeWithFields;

Rubberduck.Parsing/Rubberduck.Parsing.csproj

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@
2323
<DebugType>full</DebugType>
2424
<Optimize>false</Optimize>
2525
<OutputPath>bin\Debug\</OutputPath>
26-
<DefineConstants>DEBUG;TRACE</DefineConstants>
26+
<DefineConstants>TRACE;DEBUG</DefineConstants>
2727
<ErrorReport>prompt</ErrorReport>
2828
<WarningLevel>1</WarningLevel>
2929
<UseVSHostingProcess>true</UseVSHostingProcess>

Rubberduck.Parsing/Symbols/DeclarationSymbolsListener.cs

Lines changed: 33 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -136,41 +136,43 @@ private IEnumerable<IAnnotation> FindAnnotations(int line)
136136
/// </remarks>
137137
private void DeclareControlsAsMembers(IVBComponent form)
138138
{
139-
if (form.Controls == null) { return; }
140-
141-
var libraryQualifier = string.Empty;
142-
if (_qualifiedModuleName.ComponentType == ComponentType.UserForm)
139+
using (var controls = form.Controls)
143140
{
144-
var msFormsLib = _state.DeclarationFinder.FindProject("MSForms");
145-
//Debug.Assert(msFormsLib != null);
146-
if (msFormsLib != null)
141+
if (controls == null) { return; }
142+
143+
var libraryQualifier = string.Empty;
144+
if (_qualifiedModuleName.ComponentType == ComponentType.UserForm)
147145
{
148-
// given a UserForm component, MSForms reference is in use and cannot be removed.
149-
libraryQualifier = "MSForms.";
146+
var msFormsLib = _state.DeclarationFinder.FindProject("MSForms");
147+
if (msFormsLib != null)
148+
{
149+
// given a UserForm component, MSForms reference is in use and cannot be removed.
150+
libraryQualifier = "MSForms.";
151+
}
150152
}
151-
}
152-
153-
foreach (var control in form.Controls)
154-
{
155-
var typeName = $"{libraryQualifier}{control.TypeName()}";
156-
// The as type declaration should be TextBox, CheckBox, etc. depending on the type.
157-
var declaration = new Declaration(
158-
_qualifiedModuleName.QualifyMemberName(control.Name),
159-
_parentDeclaration,
160-
_currentScopeDeclaration,
161-
string.IsNullOrEmpty(typeName) ? "Control" : typeName,
162-
null,
163-
true,
164-
true,
165-
Accessibility.Public,
166-
DeclarationType.Control,
167-
null,
168-
Selection.Home,
169-
false,
170-
null,
171-
true);
172153

173-
AddDeclaration(declaration);
154+
foreach (var control in controls)
155+
{
156+
var typeName = $"{libraryQualifier}{control.TypeName()}";
157+
// The as type declaration should be TextBox, CheckBox, etc. depending on the type.
158+
var declaration = new Declaration(
159+
_qualifiedModuleName.QualifyMemberName(control.Name),
160+
_parentDeclaration,
161+
_currentScopeDeclaration,
162+
string.IsNullOrEmpty(typeName) ? "Control" : typeName,
163+
null,
164+
true,
165+
true,
166+
Accessibility.Public,
167+
DeclarationType.Control,
168+
null,
169+
Selection.Home,
170+
false,
171+
null,
172+
true);
173+
174+
AddDeclaration(declaration);
175+
}
174176
}
175177
}
176178

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1023,12 +1023,20 @@ public bool IsNewOrModified(QualifiedModuleName key)
10231023
private int GetModuleContentHash(QualifiedModuleName module)
10241024
{
10251025
var component = ProjectsProvider.Component(module);
1026-
return QualifiedModuleName.GetModuleContentHash(component);
1026+
return QualifiedModuleName.GetContentHash(component);
10271027
}
10281028

10291029
public Declaration FindSelectedDeclaration(ICodePane activeCodePane)
10301030
{
1031-
return DeclarationFinder?.FindSelectedDeclaration(activeCodePane);
1031+
if (activeCodePane != null)
1032+
{
1033+
return DeclarationFinder?.FindSelectedDeclaration(activeCodePane);
1034+
}
1035+
1036+
using (var active = _vbe.ActiveCodePane)
1037+
{
1038+
return DeclarationFinder?.FindSelectedDeclaration(active);
1039+
}
10321040
}
10331041

10341042
public void RemoveBuiltInDeclarations(IReference reference)

Rubberduck.VBEEditor/Events/AutoCompleteEventArgs.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ namespace Rubberduck.VBEditor.Events
66
{
77
public class AutoCompleteEventArgs : EventArgs
88
{
9-
public AutoCompleteEventArgs(ICodeModule module, WindowsApi.KeyPressEventArgs e)
9+
public AutoCompleteEventArgs(ICodeModule module, KeyPressEventArgs e)
1010
{
1111
if (e.Key == Keys.Delete ||
1212
e.Key == Keys.Back ||

0 commit comments

Comments
 (0)