Skip to content

Commit 5f77e03

Browse files
committed
Reimplement FindEventHandlers taking an event declaration in the DeclarationFinder
1 parent cb34855 commit 5f77e03

File tree

7 files changed

+35
-66
lines changed

7 files changed

+35
-66
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterCanBeByValInspection.cs

Lines changed: 1 addition & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
using System.Collections.Generic;
33
using System.Diagnostics;
44
using System.Linq;
5-
using Rubberduck.Common;
65
using Rubberduck.Inspections.Abstract;
76
using Rubberduck.Inspections.Results;
87
using Rubberduck.Parsing;
@@ -12,7 +11,6 @@
1211
using Rubberduck.Parsing.Symbols;
1312
using Rubberduck.Parsing.VBA;
1413
using Rubberduck.Parsing.VBA.Extensions;
15-
using Rubberduck.Inspections.Inspections.Extensions;
1614

1715
namespace Rubberduck.Inspections.Concrete
1816
{
@@ -157,11 +155,8 @@ private IEnumerable<ParameterDeclaration> EventMembersThatCanBeChangedToBePassed
157155

158156
var parameterCanBeChangedToBeByVal = eventParameters.Select(parameter => parameter.IsByRef).ToList();
159157

160-
//todo: Find a better way to find the handlers.
161158
var eventHandlers = State.DeclarationFinder
162-
.AllUserDeclarations
163-
.FindHandlersForEvent(memberDeclaration)
164-
.Select(s => s.Item2)
159+
.FindEventHandlers(memberDeclaration)
165160
.ToList();
166161

167162
foreach (var eventHandler in eventHandlers.OfType<IParameterizedDeclaration>())

Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using System.Collections.Generic;
22
using System.Linq;
33
using Antlr4.Runtime;
4-
using Rubberduck.Common;
54
using Rubberduck.Inspections.Abstract;
65
using Rubberduck.Inspections.Results;
76
using Rubberduck.Parsing;
@@ -11,7 +10,6 @@
1110
using Rubberduck.Parsing.Symbols;
1211
using Rubberduck.Parsing.VBA;
1312
using Rubberduck.VBEditor;
14-
using Rubberduck.Inspections.Inspections.Extensions;
1513

1614
namespace Rubberduck.Inspections.Concrete
1715
{

Rubberduck.CodeAnalysis/QuickFixes/PassParameterByValueQuickFix.cs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
using System.Linq;
2-
using Rubberduck.Common;
32
using Rubberduck.Inspections.Abstract;
43
using Rubberduck.Inspections.Concrete;
54
using Rubberduck.Parsing.Grammar;
@@ -52,12 +51,14 @@ private void FixMethods(Declaration target, IRewriteSession rewriteSession)
5251
return; // should only happen if the parse results are stale; prevents a crash in that case
5352
}
5453

55-
//FIXME: Make this use the DeclarationFinder.
5654
var members = target.ParentDeclaration.DeclarationType == DeclarationType.Event
57-
? _state.AllUserDeclarations.FindHandlersForEvent(target.ParentDeclaration)
58-
.Select(s => s.Item2)
55+
? _state.DeclarationFinder
56+
.FindEventHandlers(target.ParentDeclaration)
5957
.ToList()
60-
: _state.DeclarationFinder.FindInterfaceImplementationMembers(target.ParentDeclaration).Cast<Declaration>().ToList();
58+
: _state.DeclarationFinder
59+
.FindInterfaceImplementationMembers(target.ParentDeclaration)
60+
.Cast<Declaration>()
61+
.ToList();
6162

6263
foreach (var member in members)
6364
{

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

Lines changed: 19 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -306,7 +306,15 @@ public IEnumerable<Declaration> FindEventHandlers()
306306
{
307307
return _eventHandlers.Value;
308308
}
309-
309+
310+
public IEnumerable<Declaration> FindEventHandlers(Declaration eventDeclaration)
311+
{
312+
var withEventsDeclarations = FindWithEventFields(eventDeclaration);
313+
return withEventsDeclarations
314+
.Select(withEventsField => FindHandlersForWithEventsField(withEventsField)
315+
.Single(handler => handler.IdentifierName == $"{withEventsField.IdentifierName}_{eventDeclaration.IdentifierName}"));
316+
}
317+
310318
public IEnumerable<Declaration> FindFormControlEventHandlers()
311319
{
312320
return _controlEventHandlers.Value;
@@ -361,6 +369,16 @@ public IEnumerable<Declaration> FindHandlersForWithEventsField(Declaration field
361369
: Enumerable.Empty<Declaration>();
362370
}
363371

372+
public IEnumerable<Declaration> FindWithEventFields()
373+
{
374+
return _handlersByWithEventsField.Value.Keys;
375+
}
376+
377+
public IEnumerable<Declaration> FindWithEventFields(Declaration eventDeclaration)
378+
{
379+
return FindWithEventFields().Where(withEventField => withEventField.AsTypeName == eventDeclaration.ComponentName);
380+
}
381+
364382
/// <summary>
365383
/// Finds all members of a class that are implementing the interface defined by the passed context.
366384
/// </summary>

Rubberduck.Refactorings/Common/DeclarationExtensions.cs

Lines changed: 0 additions & 36 deletions
This file was deleted.

Rubberduck.Refactorings/RemoveParameters/RemoveParametersRefactoring.cs

Lines changed: 5 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
using System.Collections.Generic;
22
using System.Linq;
3-
using Rubberduck.Common;
43
using Rubberduck.Parsing;
54
using Rubberduck.Parsing.Grammar;
65
using Rubberduck.Parsing.Rewriter;
@@ -84,17 +83,16 @@ private static RemoveParametersModel ResolvedInterfaceMemberTarget(RemoveParamet
8483

8584
private RemoveParametersModel ResolvedEventTarget(RemoveParametersModel model)
8685
{
87-
foreach (var events in _declarationFinderProvider
86+
foreach (var eventDeclaration in _declarationFinderProvider
8887
.DeclarationFinder
8988
.UserDeclarations(DeclarationType.Event))
9089
{
9190
if (_declarationFinderProvider.DeclarationFinder
92-
.AllUserDeclarations
93-
.FindHandlersForEvent(events)
94-
.Any(reference => Equals(reference.Item2, model.TargetDeclaration)))
91+
.FindEventHandlers(eventDeclaration)
92+
.Any(handler => Equals(handler, model.TargetDeclaration)))
9593
{
9694
model.IsEventRefactoring = true;
97-
model.TargetDeclaration = events;
95+
model.TargetDeclaration = eventDeclaration;
9896
return model;
9997
}
10098
}
@@ -289,10 +287,7 @@ private void AdjustSignatures(RemoveParametersModel model, IRewriteSession rewri
289287
RemoveSignatureParameters(model, model.TargetDeclaration, rewriteSession);
290288

291289
var eventImplementations = _declarationFinderProvider.DeclarationFinder
292-
.AllUserDeclarations
293-
.Where(item => item.IsWithEvents && item.AsTypeName == model.TargetDeclaration.ComponentName)
294-
.SelectMany(withEvents => _declarationFinderProvider.DeclarationFinder
295-
.FindHandlersForWithEventsField(withEvents));
290+
.FindEventHandlers(model.TargetDeclaration);
296291

297292
foreach (var eventImplementation in eventImplementations)
298293
{

Rubberduck.Refactorings/ReorderParameters/ReorderParametersRefactoring.cs

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@
55
using Rubberduck.Parsing.Rewriter;
66
using System.Collections.Generic;
77
using System.Linq;
8-
using Rubberduck.Common;
98
using Rubberduck.Parsing.VBA;
109
using Rubberduck.Refactorings.Exceptions;
1110
using Rubberduck.VBEditor.Utility;
@@ -83,17 +82,16 @@ private static ReorderParametersModel ResolvedInterfaceMemberTarget(ReorderParam
8382

8483
private ReorderParametersModel ResolvedEventTarget(ReorderParametersModel model)
8584
{
86-
foreach (var events in _declarationFinderProvider
85+
foreach (var eventDeclaration in _declarationFinderProvider
8786
.DeclarationFinder
8887
.UserDeclarations(DeclarationType.Event))
8988
{
9089
if (_declarationFinderProvider.DeclarationFinder
91-
.AllUserDeclarations
92-
.FindHandlersForEvent(events)
93-
.Any(reference => Equals(reference.Item2, model.TargetDeclaration)))
90+
.FindEventHandlers(eventDeclaration)
91+
.Any(handler => Equals(handler, model.TargetDeclaration)))
9492
{
9593
model.IsEventRefactoring = true;
96-
model.TargetDeclaration = events;
94+
model.TargetDeclaration = eventDeclaration;
9795
return model;
9896
}
9997
}

0 commit comments

Comments
 (0)