Skip to content

Commit 6cac10d

Browse files
committed
Remove FindControlEventHandlers from DeclarationExtensions
1 parent 2786f1e commit 6cac10d

File tree

3 files changed

+23
-44
lines changed

3 files changed

+23
-44
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureNotUsedInspection.cs

Lines changed: 6 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@
88
using Rubberduck.Resources.Inspections;
99
using Rubberduck.Parsing.Symbols;
1010
using Rubberduck.Parsing.VBA;
11+
using Rubberduck.Parsing.VBA.Extensions;
1112
using Rubberduck.VBEditor.SafeComWrappers;
1213

1314
namespace Rubberduck.Inspections.Concrete
@@ -59,40 +60,19 @@ public ProcedureNotUsedInspection(RubberduckParserState state) : base(state) { }
5960

6061
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
6162
{
62-
var declarations = UserDeclarations.ToList();
63-
6463
var classes = State.DeclarationFinder.UserDeclarations(DeclarationType.ClassModule)
6564
.Concat(State.DeclarationFinder.UserDeclarations(DeclarationType.Document))
6665
.ToList();
6766
var modules = State.DeclarationFinder.UserDeclarations(DeclarationType.ProceduralModule).ToList();
6867

69-
var handlers = State.DeclarationFinder.UserDeclarations(DeclarationType.Control)
70-
.SelectMany(control => declarations.FindEventHandlers(control)).ToList();
68+
var handlers = State.DeclarationFinder.FindEventHandlers().ToHashSet();
7169

72-
var builtInHandlers = State.DeclarationFinder.FindEventHandlers();
73-
handlers.AddRange(builtInHandlers);
70+
var interfaceMembers = State.DeclarationFinder.FindAllInterfaceMembers().ToHashSet();
71+
var implementingMembers = State.DeclarationFinder.FindAllInterfaceImplementingMembers().ToHashSet();
7472

75-
var withEventFields = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable).Where(item => item.IsWithEvents).ToList();
76-
var withHanders = withEventFields
77-
.SelectMany(field => State.DeclarationFinder.FindHandlersForWithEventsField(field))
73+
var items = State.AllUserDeclarations
74+
.Where(item => !IsIgnoredDeclaration(item, interfaceMembers, implementingMembers, handlers, classes, modules))
7875
.ToList();
79-
80-
handlers.AddRange(withHanders);
81-
82-
var forms = State.DeclarationFinder.UserDeclarations(DeclarationType.ClassModule)
83-
.Where(item => item.QualifiedName.QualifiedModuleName.ComponentType == ComponentType.UserForm)
84-
.ToList();
85-
86-
if (forms.Any())
87-
{
88-
handlers.AddRange(forms.SelectMany(form => State.FindFormEventHandlers(form)));
89-
}
90-
91-
var interfaceMembers = State.DeclarationFinder.FindAllInterfaceMembers().ToList();
92-
var implementingMembers = State.DeclarationFinder.FindAllInterfaceImplementingMembers().ToList();
93-
94-
var items = declarations
95-
.Where(item => !IsIgnoredDeclaration(item, interfaceMembers, implementingMembers, handlers, classes, modules)).ToList();
9676
var issues = items.Select(issue => new DeclarationInspectionResult(this,
9777
string.Format(InspectionResults.IdentifierNotUsedInspection, issue.DeclarationType.ToLocalizedString(), issue.IdentifierName),
9878
issue));

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

Lines changed: 17 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,7 @@ public class DeclarationFinder
5151

5252
private Lazy<List<Declaration>> _nonBaseAsType;
5353
private Lazy<List<Declaration>> _eventHandlers;
54+
private Lazy<List<Declaration>> _controlEventHandlers;
5455
private Lazy<List<Declaration>> _projects;
5556
private Lazy<List<Declaration>> _classes;
5657

@@ -165,6 +166,7 @@ private void InitializeLazyCollections()
165166
, true);
166167

167168
_eventHandlers = new Lazy<List<Declaration>>(FindAllEventHandlers, true);
169+
_controlEventHandlers = new Lazy<List<Declaration>>(FindAllFormControlHandlers, true);
168170
_projects = new Lazy<List<Declaration>>(() => DeclarationsWithType(DeclarationType.Project).ToList(), true);
169171
_classes = new Lazy<List<Declaration>>(() => DeclarationsWithType(DeclarationType.ClassModule).ToList(), true);
170172
_handlersByWithEventsField = new Lazy<IDictionary<Declaration, List<Declaration>>>(FindAllHandlersByWithEventField, true);
@@ -302,6 +304,18 @@ public IEnumerable<Declaration> FindEventHandlers()
302304
return _eventHandlers.Value;
303305
}
304306

307+
public IEnumerable<Declaration> FindFormControlEventHandlers()
308+
{
309+
return _controlEventHandlers.Value;
310+
}
311+
312+
public IEnumerable<Declaration> FindFormControlEventHandlers(Declaration control)
313+
{
314+
return _eventHandlers.Value
315+
.Where(handlers=> handlers.ParentScope == control.ParentScope
316+
&& handlers.IdentifierName.StartsWith(control.IdentifierName + "_"));
317+
}
318+
305319
public IEnumerable<Declaration> Classes => _classes.Value;
306320
public IEnumerable<Declaration> Projects => _projects.Value;
307321

@@ -1165,15 +1179,15 @@ private IEnumerable<Declaration> FindAllInReferencedProjectByPriority(Declaratio
11651179
}
11661180
}
11671181

1168-
private IEnumerable<Declaration> FindAllFormControlHandlers()
1182+
private List<Declaration> FindAllFormControlHandlers()
11691183
{
11701184
var controls = DeclarationsWithType(DeclarationType.Control);
11711185
var handlerNames = BuiltInDeclarations(DeclarationType.Event)
11721186
.SelectMany(e => controls.Select(c => c.IdentifierName + "_" + e.IdentifierName))
11731187
.ToHashSet();
11741188
var handlers = UserDeclarations(DeclarationType.Procedure)
11751189
.Where(procedure => handlerNames.Contains(procedure.IdentifierName));
1176-
return handlers;
1190+
return handlers.ToList();
11771191
}
11781192

11791193
private List<Declaration> FindAllEventHandlers()
@@ -1197,7 +1211,7 @@ private List<Declaration> FindAllEventHandlers()
11971211
.Where(item => handlerNames.Contains(item.IdentifierName))
11981212
)
11991213
.Concat(_handlersByWithEventsField.Value.AllValues())
1200-
.Concat(FindAllFormControlHandlers());
1214+
.Concat(FindFormControlEventHandlers());
12011215
return handlers.ToList();
12021216

12031217
// Local functions to help break up the complex logic in finding built-in handlers

Rubberduck.Refactorings/Common/DeclarationExtensions.cs

Lines changed: 0 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,29 +1,14 @@
11
using System;
22
using System.Collections.Generic;
3-
using System.Diagnostics;
43
using System.Linq;
54
using Rubberduck.Parsing.Symbols;
65
using Rubberduck.Parsing.VBA;
76
using Rubberduck.VBEditor.SafeComWrappers;
87

9-
// ReSharper disable LocalizableElement
10-
118
namespace Rubberduck.Common
129
{
1310
public static class DeclarationExtensions
1411
{
15-
/// <summary>
16-
/// Finds all event handler procedures for specified control declaration.
17-
/// </summary>
18-
public static IEnumerable<Declaration> FindEventHandlers(this IEnumerable<Declaration> declarations, Declaration control)
19-
{
20-
Debug.Assert(control.DeclarationType == DeclarationType.Control);
21-
22-
return declarations.Where(declaration => declaration.ParentScope == control.ParentScope
23-
&& declaration.DeclarationType == DeclarationType.Procedure
24-
&& declaration.IdentifierName.StartsWith(control.IdentifierName + "_"));
25-
}
26-
2712
public static IEnumerable<Declaration> FindUserEventHandlers(this IEnumerable<Declaration> declarations)
2813
{
2914
var declarationList = declarations.ToList();

0 commit comments

Comments
 (0)