10
10
using Antlr4 . Runtime ;
11
11
using Rubberduck . Parsing . Grammar ;
12
12
using Rubberduck . VBEditor . Application ;
13
+ using Rubberduck . VBEditor . SafeComWrappers . Abstract ;
13
14
14
15
namespace Rubberduck . Parsing . Symbols
15
16
{
@@ -48,6 +49,8 @@ public class DeclarationFinder
48
49
private readonly ConcurrentDictionary < QualifiedModuleName , ConcurrentBag < IAnnotation > > _annotations ;
49
50
private readonly ConcurrentDictionary < Declaration , ConcurrentBag < Declaration > > _parametersByParent ;
50
51
private readonly ConcurrentDictionary < DeclarationType , ConcurrentBag < Declaration > > _userDeclarationsByType ;
52
+ private readonly IDictionary < QualifiedSelection , IEnumerable < Declaration > > _declarationsBySelection ;
53
+ private readonly IDictionary < QualifiedSelection , IEnumerable < IdentifierReference > > _referencesBySelection ;
51
54
52
55
private readonly Lazy < ConcurrentDictionary < Declaration , Declaration [ ] > > _handlersByWithEventsField ;
53
56
private readonly Lazy < ConcurrentDictionary < VBAParser . ImplementsStmtContext , Declaration [ ] > > _membersByImplementsContext ;
@@ -58,12 +61,29 @@ public class DeclarationFinder
58
61
59
62
private readonly object threadLock = new object ( ) ;
60
63
64
+ private static QualifiedSelection GetGroupingKey ( Declaration declaration )
65
+ {
66
+ // we want the procedures' whole body, not just their identifier:
67
+ return declaration . DeclarationType . HasFlag ( DeclarationType . Member )
68
+ ? new QualifiedSelection (
69
+ declaration . QualifiedName . QualifiedModuleName ,
70
+ declaration . Context . GetSelection ( ) )
71
+ : declaration . QualifiedSelection ;
72
+ }
73
+
61
74
public DeclarationFinder ( IReadOnlyList < Declaration > declarations , IEnumerable < IAnnotation > annotations , IReadOnlyList < UnboundMemberDeclaration > unresolvedMemberDeclarations , IHostApplication hostApp = null )
62
75
{
63
76
_hostApp = hostApp ;
64
77
_annotations = annotations . GroupBy ( node => node . QualifiedSelection . QualifiedName ) . ToConcurrentDictionary ( ) ;
65
78
_declarations = declarations . GroupBy ( item => item . QualifiedName . QualifiedModuleName ) . ToConcurrentDictionary ( ) ;
66
79
_declarationsByName = declarations . GroupBy ( declaration => declaration . IdentifierName . ToLowerInvariant ( ) ) . ToConcurrentDictionary ( ) ;
80
+ _declarationsBySelection = declarations . Where ( declaration => ! declaration . IsBuiltIn )
81
+ . GroupBy ( GetGroupingKey )
82
+ . ToDictionary ( group => group . Key , group => group . AsEnumerable ( ) ) ;
83
+ _referencesBySelection = declarations
84
+ . SelectMany ( declaration => declaration . References )
85
+ . GroupBy ( reference => new QualifiedSelection ( reference . QualifiedModuleName , reference . Selection ) )
86
+ . ToDictionary ( group => group . Key , group => group . AsEnumerable ( ) ) ;
67
87
_parametersByParent = declarations . Where ( declaration => declaration . DeclarationType == DeclarationType . Parameter )
68
88
. GroupBy ( declaration => declaration . ParentDeclaration ) . ToConcurrentDictionary ( ) ;
69
89
_userDeclarationsByType = declarations . Where ( declaration => ! declaration . IsBuiltIn ) . GroupBy ( declaration => declaration . DeclarationType ) . ToConcurrentDictionary ( ) ;
@@ -148,6 +168,62 @@ public DeclarationFinder(IReadOnlyList<Declaration> declarations, IEnumerable<IA
148
168
, true ) ;
149
169
}
150
170
171
+ public Declaration FindSelectedDeclaration ( ICodePane activeCodePane )
172
+ {
173
+ if ( activeCodePane == null || activeCodePane . IsWrappingNullReference )
174
+ {
175
+ return null ;
176
+ }
177
+
178
+ var qualifiedSelection = activeCodePane . GetQualifiedSelection ( ) ;
179
+ if ( ! qualifiedSelection . HasValue || qualifiedSelection . Value . Equals ( default ( QualifiedSelection ) ) )
180
+ {
181
+ return null ;
182
+ }
183
+
184
+ var selection = qualifiedSelection . Value . Selection ;
185
+
186
+ // statistically we'll be on an IdentifierReference more often than on a Declaration:
187
+ var matches = _referencesBySelection
188
+ . Where ( kvp => kvp . Key . QualifiedName . Equals ( qualifiedSelection . Value . QualifiedName )
189
+ && kvp . Key . Selection . ContainsFirstCharacter ( qualifiedSelection . Value . Selection ) )
190
+ . SelectMany ( kvp => kvp . Value )
191
+ . OrderByDescending ( reference => reference . Declaration . DeclarationType )
192
+ . Select ( reference => reference . Declaration )
193
+ . Distinct ( )
194
+ . ToArray ( ) ;
195
+
196
+ if ( ! matches . Any ( ) )
197
+ {
198
+ matches = _declarationsBySelection
199
+ . Where ( kvp => kvp . Key . QualifiedName . Equals ( qualifiedSelection . Value . QualifiedName )
200
+ && kvp . Key . Selection . ContainsFirstCharacter ( selection ) )
201
+ . SelectMany ( kvp => kvp . Value )
202
+ . OrderByDescending ( declaration => declaration . DeclarationType )
203
+ . Distinct ( )
204
+ . ToArray ( ) ;
205
+ }
206
+
207
+ switch ( matches . Length )
208
+ {
209
+ case 0 :
210
+ ConcurrentBag < Declaration > modules ;
211
+ return _declarations . TryGetValue ( qualifiedSelection . Value . QualifiedName , out modules )
212
+ ? modules . SingleOrDefault ( declaration => declaration . DeclarationType . HasFlag ( DeclarationType . Module ) )
213
+ : null ;
214
+
215
+ case 1 :
216
+ var match = matches . Single ( ) ;
217
+ return match . DeclarationType == DeclarationType . ModuleOption
218
+ ? match . ParentScopeDeclaration
219
+ : match ;
220
+
221
+ default :
222
+ // they're sorted by type, so a local comes before the procedure it's in
223
+ return matches . FirstOrDefault ( ) ;
224
+ }
225
+ }
226
+
151
227
public IEnumerable < Declaration > FreshUndeclared
152
228
{
153
229
get { return _newUndeclared . AllValues ( ) ; }
0 commit comments