Skip to content

Commit cb34855

Browse files
committed
Replace further methods in DeclarationExtensions with calls to members of DeclarationFinder
1 parent 6cac10d commit cb34855

File tree

6 files changed

+40
-94
lines changed

6 files changed

+40
-94
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterCanBeByValInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -61,8 +61,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
6161
parametersThatCanBeChangedToBePassedByVal.AddRange(InterFaceMembersThatCanBeChangedToBePassedByVal(interfaceDeclarationMembers));
6262

6363
var eventMembers = State.DeclarationFinder.UserDeclarations(DeclarationType.Event).ToList();
64-
var formEventHandlerScopeDeclarations = State.FindFormEventHandlers();
65-
var eventHandlerScopeDeclarations = State.DeclarationFinder.FindEventHandlers().Concat(parameters.FindUserEventHandlers());
64+
var formEventHandlerScopeDeclarations = State.DeclarationFinder.FindFormEventHandlers();
65+
var eventHandlerScopeDeclarations = State.DeclarationFinder.FindEventHandlers();
6666
var eventScopeDeclarations = eventMembers
6767
.Concat(formEventHandlerScopeDeclarations)
6868
.Concat(eventHandlerScopeDeclarations)

Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -71,21 +71,20 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
7171
return Listener.Contexts
7272
.Where(context => context.Context.Parent is VBAParser.SubStmtContext
7373
&& HasArgumentReferencesWithIsAssignmentFlagged(context))
74-
.Select(context => GetSubStmtParentDeclaration(context))
74+
.Select(GetSubStmtParentDeclaration)
7575
.Where(decl => decl != null &&
7676
!ignored.Contains(decl) &&
7777
userDeclarations.Where(item => item.IsWithEvents)
78-
.All(withEvents => userDeclarations.FindEventProcedures(withEvents) == null) &&
78+
.All(withEvents => !State.DeclarationFinder.FindHandlersForWithEventsField(withEvents).Any()) &&
7979
!builtinHandlers.Contains(decl))
8080
.Select(result => new DeclarationInspectionResult(this,
8181
string.Format(InspectionResults.ProcedureCanBeWrittenAsFunctionInspection, result.IdentifierName),
8282
result));
8383

8484
bool HasArgumentReferencesWithIsAssignmentFlagged(QualifiedContext<ParserRuleContext> context)
8585
{
86-
return contextLookup.TryGetValue(context.Context.GetChild<VBAParser.ArgContext>(), out Declaration decl)
87-
? decl.References.Any(rf => rf.IsAssignment)
88-
: false;
86+
return contextLookup.TryGetValue(context.Context.GetChild<VBAParser.ArgContext>(), out Declaration decl)
87+
&& decl.References.Any(rf => rf.IsAssignment);
8988
}
9089

9190
Declaration GetSubStmtParentDeclaration(QualifiedContext<ParserRuleContext> context)

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

Lines changed: 32 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@
1313
using Rubberduck.Parsing.VBA.ReferenceManagement;
1414
using Rubberduck.VBEditor;
1515
using Rubberduck.VBEditor.Extensions;
16+
using Rubberduck.VBEditor.SafeComWrappers;
1617
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1718

1819
namespace Rubberduck.Parsing.VBA.DeclarationCaching
@@ -49,9 +50,10 @@ public class DeclarationFinder
4950
private Lazy<IDictionary<ClassModuleDeclaration, List<ClassModuleDeclaration>>> _interfaceImplementations;
5051
private Lazy<IDictionary<IInterfaceExposable, List<ModuleBodyElementDeclaration>>> _implementationsByMember;
5152

52-
private Lazy<List<Declaration>> _nonBaseAsType;
53+
private Lazy<List<Declaration>> _nonBaseAsType;
5354
private Lazy<List<Declaration>> _eventHandlers;
5455
private Lazy<List<Declaration>> _controlEventHandlers;
56+
private Lazy<List<Declaration>> _formEventHandlers;
5557
private Lazy<List<Declaration>> _projects;
5658
private Lazy<List<Declaration>> _classes;
5759

@@ -167,12 +169,13 @@ private void InitializeLazyCollections()
167169

168170
_eventHandlers = new Lazy<List<Declaration>>(FindAllEventHandlers, true);
169171
_controlEventHandlers = new Lazy<List<Declaration>>(FindAllFormControlHandlers, true);
172+
_formEventHandlers = new Lazy<List<Declaration>>(FindAllFormEventHandlers, true);
170173
_projects = new Lazy<List<Declaration>>(() => DeclarationsWithType(DeclarationType.Project).ToList(), true);
171174
_classes = new Lazy<List<Declaration>>(() => DeclarationsWithType(DeclarationType.ClassModule).ToList(), true);
172175
_handlersByWithEventsField = new Lazy<IDictionary<Declaration, List<Declaration>>>(FindAllHandlersByWithEventField, true);
173176

174177
_implementingMembers = new Lazy<IDictionary<(VBAParser.ImplementsStmtContext Context, Declaration Implementor), List<ModuleBodyElementDeclaration>>>(FindAllImplementingMembers, true);
175-
_interfaceMembers = new Lazy<IDictionary<ClassModuleDeclaration, List<Declaration>>>(FindAllIinterfaceMembersByModule, true);
178+
_interfaceMembers = new Lazy<IDictionary<ClassModuleDeclaration, List<Declaration>>>(FindAllInterfaceMembersByModule, true);
176179
_membersByImplementsContext = new Lazy<IDictionary<VBAParser.ImplementsStmtContext, List<ModuleBodyElementDeclaration>>>(FindAllImplementingMembersByImplementsContext, true);
177180
_interfaceImplementations = new Lazy<IDictionary<ClassModuleDeclaration, List<ClassModuleDeclaration>>>(FindAllImplementionsByInterface, true);
178181
_implementationsByMember = new Lazy<IDictionary<IInterfaceExposable, List<ModuleBodyElementDeclaration>>>(FindAllImplementingMembersByMember, true);
@@ -233,7 +236,7 @@ private IDictionary<IInterfaceExposable, List<ModuleBodyElementDeclaration>> Fin
233236
return _implementingMembers.Value.ToDictionary(pair => pair.Key.Context, pair => pair.Value);
234237
}
235238

236-
private IDictionary<ClassModuleDeclaration, List<Declaration>> FindAllIinterfaceMembersByModule()
239+
private IDictionary<ClassModuleDeclaration, List<Declaration>> FindAllInterfaceMembersByModule()
237240
{
238241
return UserDeclarations(DeclarationType.ClassModule)
239242
.Concat(UserDeclarations(DeclarationType.Document))
@@ -303,7 +306,7 @@ public IEnumerable<Declaration> FindEventHandlers()
303306
{
304307
return _eventHandlers.Value;
305308
}
306-
309+
307310
public IEnumerable<Declaration> FindFormControlEventHandlers()
308311
{
309312
return _controlEventHandlers.Value;
@@ -316,6 +319,11 @@ public IEnumerable<Declaration> FindFormControlEventHandlers(Declaration control
316319
&& handlers.IdentifierName.StartsWith(control.IdentifierName + "_"));
317320
}
318321

322+
public IEnumerable<Declaration> FindFormEventHandlers()
323+
{
324+
return _formEventHandlers.Value;
325+
}
326+
319327
public IEnumerable<Declaration> Classes => _classes.Value;
320328
public IEnumerable<Declaration> Projects => _projects.Value;
321329

@@ -1211,7 +1219,8 @@ private List<Declaration> FindAllEventHandlers()
12111219
.Where(item => handlerNames.Contains(item.IdentifierName))
12121220
)
12131221
.Concat(_handlersByWithEventsField.Value.AllValues())
1214-
.Concat(FindFormControlEventHandlers());
1222+
.Concat(FindFormControlEventHandlers())
1223+
.Concat(FindFormEventHandlers());
12151224
return handlers.ToList();
12161225

12171226
// Local functions to help break up the complex logic in finding built-in handlers
@@ -1234,6 +1243,24 @@ bool IsHostSpecificHandler(Declaration item)
12341243
}
12351244
}
12361245

1246+
private List<Declaration> FindAllFormEventHandlers()
1247+
{
1248+
var forms = DeclarationsWithType(DeclarationType.ClassModule).
1249+
Where(declaration => declaration.QualifiedModuleName.ComponentType == ComponentType.UserForm);
1250+
var formScopes = forms
1251+
.Select(form => form.Scope)
1252+
.ToHashSet();
1253+
var events = BuiltInDeclarations(DeclarationType.Event)
1254+
.Where(item => item.ParentScope == "FM20.DLL;MSForms.FormEvents");
1255+
var handlerNames = events
1256+
.Select(item => "UserForm_" + item.IdentifierName)
1257+
.ToHashSet();
1258+
var handlers = UserDeclarations(DeclarationType.Procedure)
1259+
.Where(procedure => handlerNames.Contains(procedure.IdentifierName)
1260+
&& formScopes.Contains(procedure.ParentScope));
1261+
return handlers.ToList();
1262+
}
1263+
12371264
/// <summary>
12381265
/// Finds declarations that would be in conflict with the target declaration if renamed.
12391266
/// </summary>

Rubberduck.Refactorings/Common/DeclarationExtensions.cs

Lines changed: 0 additions & 79 deletions
Original file line numberDiff line numberDiff line change
@@ -2,61 +2,11 @@
22
using System.Collections.Generic;
33
using System.Linq;
44
using Rubberduck.Parsing.Symbols;
5-
using Rubberduck.Parsing.VBA;
6-
using Rubberduck.VBEditor.SafeComWrappers;
75

86
namespace Rubberduck.Common
97
{
108
public static class DeclarationExtensions
119
{
12-
public static IEnumerable<Declaration> FindUserEventHandlers(this IEnumerable<Declaration> declarations)
13-
{
14-
var declarationList = declarations.ToList();
15-
16-
var userEvents =
17-
declarationList.Where(item => item.IsUserDefined && item.DeclarationType == DeclarationType.Event).ToList();
18-
19-
var handlers = new List<Declaration>();
20-
foreach (var @event in userEvents)
21-
{
22-
handlers.AddRange(declarationList.FindHandlersForEvent(@event).Select(s => s.Item2));
23-
}
24-
25-
return handlers;
26-
}
27-
28-
public static IEnumerable<Declaration> FindFormEventHandlers(this RubberduckParserState state)
29-
{
30-
var items = state.AllDeclarations.ToList();
31-
32-
var forms = items.Where(item => item.DeclarationType == DeclarationType.ClassModule
33-
&& item.QualifiedName.QualifiedModuleName.ComponentType == ComponentType.UserForm)
34-
.ToList();
35-
36-
var result = new List<Declaration>();
37-
foreach (var declaration in forms)
38-
{
39-
result.AddRange(FindFormEventHandlers(state, declaration));
40-
}
41-
42-
return result;
43-
}
44-
45-
public static IEnumerable<Declaration> FindFormEventHandlers(this RubberduckParserState state, Declaration userForm)
46-
{
47-
var items = state.AllDeclarations.ToList();
48-
var events = items.Where(item => !item.IsUserDefined
49-
&& item.ParentScope == "FM20.DLL;MSForms.FormEvents"
50-
&& item.DeclarationType == DeclarationType.Event).ToList();
51-
52-
var handlerNames = events.Select(item => "UserForm_" + item.IdentifierName);
53-
var handlers = items.Where(item => item.ParentScope == userForm.Scope
54-
&& item.DeclarationType == DeclarationType.Procedure
55-
&& handlerNames.Contains(item.IdentifierName));
56-
57-
return handlers.ToList();
58-
}
59-
6010
/// <summary>
6111
/// Gets a tuple containing the <c>WithEvents</c> declaration and the corresponding handler,
6212
/// for each type implementing this event.
@@ -82,34 +32,5 @@ public static IEnumerable<Tuple<Declaration,Declaration>> FindHandlersForEvent(t
8232
&& declaration.IdentifierName == item.WithEventsDeclaration.IdentifierName + '_' + eventDeclaration.IdentifierName)
8333
));
8434
}
85-
86-
public static IEnumerable<Declaration> FindEventProcedures(this IEnumerable<Declaration> declarations, Declaration withEventsDeclaration)
87-
{
88-
if (!withEventsDeclaration.IsWithEvents)
89-
{
90-
return new Declaration[]{};
91-
}
92-
93-
var items = declarations as IList<Declaration> ?? declarations.ToList();
94-
var type = withEventsDeclaration.AsTypeDeclaration;
95-
96-
if (type == null)
97-
{
98-
return new Declaration[]{};
99-
}
100-
101-
var members = items
102-
.Where(item => Equals(item.ParentScopeDeclaration, type))
103-
.ToList();
104-
var events = members.Where(member => member.DeclarationType == DeclarationType.Event);
105-
var handlerNames = events.Select(e => withEventsDeclaration.IdentifierName + '_' + e.IdentifierName);
106-
107-
return items.Where(item => item.Project != null
108-
&& item.ProjectId == withEventsDeclaration.ProjectId
109-
&& item.ParentScope == withEventsDeclaration.ParentScope
110-
&& item.DeclarationType == DeclarationType.Procedure
111-
&& handlerNames.Any(name => item.IdentifierName == name))
112-
.ToList();
113-
}
11435
}
11536
}

Rubberduck.Refactorings/RemoveParameters/RemoveParametersRefactoring.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -292,7 +292,7 @@ private void AdjustSignatures(RemoveParametersModel model, IRewriteSession rewri
292292
.AllUserDeclarations
293293
.Where(item => item.IsWithEvents && item.AsTypeName == model.TargetDeclaration.ComponentName)
294294
.SelectMany(withEvents => _declarationFinderProvider.DeclarationFinder
295-
.AllUserDeclarations.FindEventProcedures(withEvents));
295+
.FindHandlersForWithEventsField(withEvents));
296296

297297
foreach (var eventImplementation in eventImplementations)
298298
{

Rubberduck.Refactorings/ReorderParameters/ReorderParametersRefactoring.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -233,8 +233,7 @@ private void AdjustSignatures(ReorderParametersModel model, IRewriteSession rewr
233233
.Where(item => item.IsWithEvents && item.AsTypeName == model.TargetDeclaration.ComponentName))
234234
{
235235
foreach (var reference in _declarationFinderProvider.DeclarationFinder
236-
.AllUserDeclarations
237-
.FindEventProcedures(withEvents))
236+
.FindHandlersForWithEventsField(withEvents))
238237
{
239238
AdjustReferences(model, reference.References, rewriteSession);
240239
AdjustSignatures(model, reference, rewriteSession);

0 commit comments

Comments
 (0)