Skip to content

Commit 42a602a

Browse files
committed
Let IdentifierReferenceInspectionResult take a DeclarationFinder instead of the provider
1 parent 13e1547 commit 42a602a

File tree

7 files changed

+38
-41
lines changed

7 files changed

+38
-41
lines changed

Rubberduck.CodeAnalysis/Inspections/Abstract/IdentifierReferenceInspectionBase.cs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -36,7 +36,7 @@ protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleN
3636
.Where(reference => IsResultReference(reference, finder));
3737

3838
return objectionableReferences
39-
.Select(reference => InspectionResult(reference, DeclarationFinderProvider))
39+
.Select(reference => InspectionResult(reference, finder))
4040
.ToList();
4141
}
4242

@@ -51,12 +51,12 @@ protected virtual IEnumerable<IdentifierReference> ReferencesInModule(QualifiedM
5151
return finder.IdentifierReferences(module);
5252
}
5353

54-
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider)
54+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, DeclarationFinder finder)
5555
{
5656
return new IdentifierReferenceInspectionResult(
5757
this,
5858
ResultDescription(reference),
59-
declarationFinderProvider,
59+
finder,
6060
reference,
6161
DisabledQuickFixes(reference));
6262
}
@@ -90,7 +90,7 @@ protected IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleN
9090
.Select(result => result.Value);
9191

9292
return objectionableReferencesWithProperties
93-
.Select(tpl => InspectionResult(tpl.reference, DeclarationFinderProvider, tpl.properties))
93+
.Select(tpl => InspectionResult(tpl.reference, finder, tpl.properties))
9494
.ToList();
9595
}
9696

@@ -113,12 +113,12 @@ protected virtual IEnumerable<IdentifierReference> ReferencesInModule(QualifiedM
113113
return finder.IdentifierReferences(module);
114114
}
115115

116-
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider, T properties)
116+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, DeclarationFinder finder, T properties)
117117
{
118118
return new IdentifierReferenceInspectionResult<T>(
119119
this,
120120
ResultDescription(reference, properties),
121-
declarationFinderProvider,
121+
finder,
122122
reference,
123123
properties,
124124
DisabledQuickFixes(reference, properties));

Rubberduck.CodeAnalysis/Inspections/Abstract/IdentifierReferenceInspectionFromDeclarationsBase.cs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2626
var objectionableReferences = ObjectionableReferences(finder);
2727
var resultReferences = ResultReferences(objectionableReferences, finder);
2828
return resultReferences
29-
.Select(reference => InspectionResult(reference, DeclarationFinderProvider))
29+
.Select(reference => InspectionResult(reference, finder))
3030
.ToList();
3131
}
3232

@@ -52,16 +52,16 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults(Qualifi
5252
.Where(reference => reference.QualifiedModuleName.Equals(module));
5353
var resultReferences = ResultReferences(objectionableReferences, finder);
5454
return resultReferences
55-
.Select(reference => InspectionResult(reference, DeclarationFinderProvider))
55+
.Select(reference => InspectionResult(reference, finder))
5656
.ToList();
5757
}
5858

59-
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider)
59+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, DeclarationFinder finder)
6060
{
6161
return new IdentifierReferenceInspectionResult(
6262
this,
6363
ResultDescription(reference),
64-
declarationFinderProvider,
64+
finder,
6565
reference,
6666
DisabledQuickFixes(reference));
6767
}
@@ -85,7 +85,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
8585
var objectionableReferences = ObjectionableReferences(finder);
8686
var resultReferences = ResultReferences(objectionableReferences, finder);
8787
return resultReferences
88-
.Select(tpl => InspectionResult(tpl.reference, DeclarationFinderProvider, tpl.properties))
88+
.Select(tpl => InspectionResult(tpl.reference, finder, tpl.properties))
8989
.ToList();
9090
}
9191

@@ -119,16 +119,16 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults(Qualifi
119119
.Where(reference => reference.QualifiedModuleName.Equals(module));
120120
var resultReferences = ResultReferences(objectionableReferences, finder);
121121
return resultReferences
122-
.Select(tpl => InspectionResult(tpl.reference, DeclarationFinderProvider, tpl.properties))
122+
.Select(tpl => InspectionResult(tpl.reference, finder, tpl.properties))
123123
.ToList();
124124
}
125125

126-
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider, T properties)
126+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, DeclarationFinder finder, T properties)
127127
{
128128
return new IdentifierReferenceInspectionResult<T>(
129129
this,
130130
ResultDescription(reference, properties),
131-
declarationFinderProvider,
131+
finder,
132132
reference,
133133
properties,
134134
DisabledQuickFixes(reference, properties));

Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectWhereProcedureIsRequiredInspection.cs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -89,7 +89,7 @@ private IEnumerable<IInspectionResult> BoundInspectionResults(QualifiedModuleNam
8989
.Where(IsResultReference);
9090

9191
return objectionableReferences
92-
.Select(reference => BoundInspectionResult(reference, DeclarationFinderProvider))
92+
.Select(reference => BoundInspectionResult(reference, finder))
9393
.ToList();
9494
}
9595

@@ -98,12 +98,12 @@ private static bool IsResultReference(IdentifierReference reference)
9898
return reference.IsProcedureCoercion;
9999
}
100100

101-
private IInspectionResult BoundInspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider)
101+
private IInspectionResult BoundInspectionResult(IdentifierReference reference, DeclarationFinder finder)
102102
{
103103
return new IdentifierReferenceInspectionResult(
104104
this,
105105
BoundResultDescription(reference),
106-
declarationFinderProvider,
106+
finder,
107107
reference);
108108
}
109109

@@ -121,17 +121,17 @@ private IEnumerable<IInspectionResult> UnboundInspectionResults(QualifiedModuleN
121121
.Where(IsResultReference);
122122

123123
return objectionableReferences
124-
.Select(reference => UnboundInspectionResult(reference, DeclarationFinderProvider))
124+
.Select(reference => UnboundInspectionResult(reference, finder))
125125
.ToList();
126126
}
127127

128-
private IInspectionResult UnboundInspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider)
128+
private IInspectionResult UnboundInspectionResult(IdentifierReference reference, DeclarationFinder finder)
129129
{
130130
var disabledQuickFixes = new List<string>{ "ExpandDefaultMemberQuickFix" };
131131
return new IdentifierReferenceInspectionResult(
132132
this,
133133
UnboundResultDescription(reference),
134-
declarationFinderProvider,
134+
finder,
135135
reference,
136136
disabledQuickFixes);
137137
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteTypeHintInspection.cs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -95,15 +95,15 @@ private IEnumerable<IInspectionResult> ReferenceResults(QualifiedModuleName modu
9595
&& reference.Declaration.IsUserDefined
9696
&& reference.HasTypeHint());
9797
return objectionableReferences
98-
.Select(reference => InspectionResult(reference, DeclarationFinderProvider));
98+
.Select(reference => InspectionResult(reference, finder));
9999
}
100100

101-
private IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider)
101+
private IInspectionResult InspectionResult(IdentifierReference reference, DeclarationFinder finder)
102102
{
103103
return new IdentifierReferenceInspectionResult(
104104
this,
105105
ResultDescription(reference),
106-
declarationFinderProvider,
106+
finder,
107107
reference);
108108
}
109109

Rubberduck.CodeAnalysis/Inspections/Concrete/SuspiciousLetAssignmentInspection.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -86,7 +86,7 @@ private IEnumerable<IInspectionResult> BoundLhsInspectionResults(QualifiedModule
8686

8787
if (rhsDefaultMemberAccess != null)
8888
{
89-
var result = InspectionResult(assignment, rhsDefaultMemberAccess, isUnbound);
89+
var result = InspectionResult(assignment, rhsDefaultMemberAccess, isUnbound, finder);
9090
results.Add(result);
9191
}
9292
}
@@ -127,15 +127,15 @@ private bool IsImplicitDefaultMemberAssignment(IdentifierReference reference)
127127
return (unboundRhsDefaultMemberAccess, true);
128128
}
129129

130-
private IInspectionResult InspectionResult(IdentifierReference lhsReference, IdentifierReference rhsReference, bool isUnbound)
130+
private IInspectionResult InspectionResult(IdentifierReference lhsReference, IdentifierReference rhsReference, bool isUnbound, DeclarationFinder finder)
131131
{
132132
var disabledQuickFixes = isUnbound
133133
? new List<string> {"ExpandDefaultMemberQuickFix"}
134134
: new List<string>();
135135
return new IdentifierReferenceInspectionResult<IdentifierReference>(
136136
this,
137137
ResultDescription(lhsReference, rhsReference),
138-
DeclarationFinderProvider,
138+
finder,
139139
lhsReference,
140140
rhsReference,
141141
disabledQuickFixes);
@@ -161,7 +161,7 @@ private IEnumerable<IInspectionResult> UnboundLhsInspectionResults(QualifiedModu
161161

162162
if (rhsDefaultMemberAccess != null)
163163
{
164-
var result = InspectionResult(assignment, rhsDefaultMemberAccess, true);
164+
var result = InspectionResult(assignment, rhsDefaultMemberAccess, true, finder);
165165
results.Add(result);
166166
}
167167
}

Rubberduck.CodeAnalysis/Inspections/Results/IdentifierReferenceInspectionResult.cs

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
using Rubberduck.Parsing.Inspections.Abstract;
66
using Rubberduck.Parsing.Symbols;
77
using Rubberduck.Parsing.VBA;
8+
using Rubberduck.Parsing.VBA.DeclarationCaching;
89
using Rubberduck.VBEditor;
910

1011
namespace Rubberduck.Inspections.Results
@@ -16,7 +17,7 @@ public class IdentifierReferenceInspectionResult : InspectionResultBase
1617
public IdentifierReferenceInspectionResult(
1718
IInspection inspection,
1819
string description,
19-
IDeclarationFinderProvider declarationFinderProvider,
20+
DeclarationFinder finder,
2021
IdentifierReference reference,
2122
ICollection<string> disabledQuickFixes = null)
2223
: base(inspection,
@@ -25,15 +26,15 @@ public IdentifierReferenceInspectionResult(
2526
reference.Context,
2627
reference.Declaration,
2728
new QualifiedSelection(reference.QualifiedModuleName, reference.Context.GetSelection()),
28-
GetQualifiedMemberName(declarationFinderProvider, reference),
29+
GetQualifiedMemberName(finder, reference),
2930
disabledQuickFixes)
3031
{
3132
Reference = reference;
3233
}
3334

34-
private static QualifiedMemberName? GetQualifiedMemberName(IDeclarationFinderProvider declarationFinderProvider, IdentifierReference reference)
35+
private static QualifiedMemberName? GetQualifiedMemberName(DeclarationFinder finder, IdentifierReference reference)
3536
{
36-
var members = declarationFinderProvider.DeclarationFinder.Members(reference.QualifiedModuleName);
37+
var members = finder.Members(reference.QualifiedModuleName);
3738
return members.SingleOrDefault(m => reference.Context.IsDescendentOf(m.Context))?.QualifiedName;
3839
}
3940

@@ -49,14 +50,14 @@ public class IdentifierReferenceInspectionResult<T> : IdentifierReferenceInspect
4950
public IdentifierReferenceInspectionResult(
5051
IInspection inspection,
5152
string description,
52-
IDeclarationFinderProvider declarationFinderProvider,
53+
DeclarationFinder finder,
5354
IdentifierReference reference,
5455
T properties,
5556
ICollection<string> disabledQuickFixes = null)
5657
: base(
5758
inspection,
5859
description,
59-
declarationFinderProvider,
60+
finder,
6061
reference,
6162
disabledQuickFixes)
6263
{

RubberduckTests/Inspections/InspectionResultTests.cs

Lines changed: 4 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -140,13 +140,11 @@ public void IdentifierRefereneceInspectionResultsAreDeemedInvalidatedIfTheModule
140140
var identifierReference = new IdentifierReference(module, null, null, "test", default, null, declaration);
141141
var modifiedModules = new HashSet<QualifiedModuleName> { declarationModule };
142142

143-
var declarationFinderProviderMock = new Mock<IDeclarationFinderProvider>();
144-
var declaratioFinder = new DeclarationFinder(
143+
var finder = new DeclarationFinder(
145144
new List<Declaration>(),
146145
new List<IParseTreeAnnotation>(),
147146
new Dictionary<QualifiedModuleName, IFailedResolutionStore>());
148-
declarationFinderProviderMock.SetupGet(m => m.DeclarationFinder).Returns(declaratioFinder);
149-
var inspectionResult = new IdentifierReferenceInspectionResult(inspectionMock.Object, string.Empty, declarationFinderProviderMock.Object, identifierReference);
147+
var inspectionResult = new IdentifierReferenceInspectionResult(inspectionMock.Object, string.Empty, finder, identifierReference);
150148

151149
Assert.IsTrue(inspectionResult.ChangesInvalidateResult(modifiedModules));
152150
}
@@ -171,13 +169,11 @@ public void IdentifierReferenceInspectionResultsAreNotDeemedInvalidatedIfNeither
171169
var identifierReference = new IdentifierReference(module, null, null, "test", default, null, declaration);
172170
var modifiedModules = new HashSet<QualifiedModuleName> { otherModule };
173171

174-
var declarationFinderProviderMock = new Mock<IDeclarationFinderProvider>();
175-
var declarationFinder = new DeclarationFinder(
172+
var finder = new DeclarationFinder(
176173
new List<Declaration>(),
177174
new List<IParseTreeAnnotation>(),
178175
new Dictionary<QualifiedModuleName, IFailedResolutionStore>());
179-
declarationFinderProviderMock.SetupGet(m => m.DeclarationFinder).Returns(declarationFinder);
180-
var inspectionResult = new IdentifierReferenceInspectionResult(inspectionMock.Object, string.Empty, declarationFinderProviderMock.Object, identifierReference);
176+
var inspectionResult = new IdentifierReferenceInspectionResult(inspectionMock.Object, string.Empty, finder, identifierReference);
181177

182178
Assert.IsFalse(inspectionResult.ChangesInvalidateResult(modifiedModules));
183179
}

0 commit comments

Comments
 (0)