6
6
using Rubberduck . VBEditor . Events ;
7
7
using Rubberduck . VBEditor . SafeComWrappers ;
8
8
using Rubberduck . VBEditor . SafeComWrappers . Abstract ;
9
+ using Rubberduck . VBEditor . WindowsApi ;
9
10
10
11
namespace Rubberduck . UI
11
12
{
@@ -33,47 +34,60 @@ public SelectionChangeService(IVBE vbe, IParseCoordinator parser)
33
34
VBENativeServices . WindowFocusChange += OnVbeFocusChanged ;
34
35
}
35
36
36
- private void OnVbeSelectionChanged ( object sender , SelectionChangedEventArgs e )
37
+ private void OnVbeSelectionChanged ( object sender , EventArgs e )
37
38
{
38
- if ( e . CodePane == null || e . CodePane . IsWrappingNullReference )
39
+ Task . Run ( ( ) =>
39
40
{
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
+ } ) ;
48
51
}
49
52
50
53
private void OnVbeFocusChanged ( object sender , WindowChangedEventArgs e )
51
54
{
52
55
if ( e . EventType == FocusType . GotFocus )
53
56
{
54
- switch ( e . Window . Type )
57
+ switch ( e . Hwnd . ToWindowType ( ) )
55
58
{
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 ( ( ) =>
59
61
{
60
- return ;
61
- }
62
- new Task ( ( ) => DispatchSelectedDesignerDeclaration ( _vbe . SelectedVBComponent ) ) . Start ( ) ;
62
+ using ( var component = _vbe . SelectedVBComponent )
63
+ {
64
+ DispatchSelectedDesignerDeclaration ( component ) ;
65
+ }
66
+ } ) ;
63
67
break ;
64
- case WindowKind . CodeWindow :
68
+ case WindowType . CodePane :
65
69
//Caret changed in a code pane.
66
- if ( e . CodePane != null && ! e . CodePane . IsWrappingNullReference )
70
+ Task . Run ( ( ) =>
67
71
{
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
+ } ) ;
70
78
break ;
71
79
}
72
80
}
73
81
else if ( e . EventType == FocusType . ChildFocus )
74
82
{
75
83
//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
+ } ) ;
77
91
}
78
92
}
79
93
@@ -103,25 +117,29 @@ private void DispatchSelectedDesignerDeclaration(IVBComponent component)
103
117
return ;
104
118
}
105
119
106
- var selectedCount = component . SelectedControls . Count ;
107
- if ( selectedCount == 1 )
120
+ using ( var selected = component . SelectedControls )
121
+ using ( var parent = component . ParentProject )
108
122
{
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 ) ;
123
140
124
- DispatchSelectedDeclaration ( new DeclarationChangedEventArgs ( null , form , component , selectedCount > 1 ) ) ;
141
+ DispatchSelectedDeclaration ( new DeclarationChangedEventArgs ( _vbe , form , selectedCount > 1 ) ) ;
142
+ }
125
143
}
126
144
127
145
private void DispatchSelectedProjectNodeDeclaration ( IVBComponent component )
@@ -131,40 +149,39 @@ private void DispatchSelectedProjectNodeDeclaration(IVBComponent component)
131
149
return ;
132
150
}
133
151
134
- if ( ( component == null || component . IsWrappingNullReference ) && ! _vbe . ActiveVBProject . IsWrappingNullReference )
152
+ using ( var active = _vbe . ActiveVBProject )
135
153
{
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 ) ) ;
140
160
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
+ }
157
178
}
158
179
}
159
180
160
181
private bool DeclarationChanged ( Declaration current )
161
182
{
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 ) ) ;
168
185
}
169
186
170
187
public void Dispose ( )
@@ -176,18 +193,26 @@ public void Dispose()
176
193
177
194
public class DeclarationChangedEventArgs : EventArgs
178
195
{
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 ; }
184
199
185
- public DeclarationChangedEventArgs ( ICodePane pane , Declaration declaration , IVBComponent component = null , bool multipleControls = false )
200
+ public DeclarationChangedEventArgs ( IVBE vbe , Declaration declaration , bool multipleControls = false )
186
201
{
187
- ActivePane = pane ;
188
202
Declaration = declaration ;
189
- VBComponent = component ;
190
203
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
+ }
191
216
}
192
217
}
193
218
}
0 commit comments