Skip to content

Commit 9584c57

Browse files
committed
Make ObsoleteTypeHintInspection more structured
1 parent 38cdac3 commit 9584c57

File tree

1 file changed

+93
-22
lines changed

1 file changed

+93
-22
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteTypeHintInspection.cs

Lines changed: 93 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -3,8 +3,11 @@
33
using Rubberduck.Inspections.Abstract;
44
using Rubberduck.Inspections.Results;
55
using Rubberduck.Parsing.Inspections.Abstract;
6+
using Rubberduck.Parsing.Symbols;
67
using Rubberduck.Resources.Inspections;
78
using Rubberduck.Parsing.VBA;
9+
using Rubberduck.Parsing.VBA.DeclarationCaching;
10+
using Rubberduck.VBEditor;
811

912
namespace Rubberduck.Inspections.Concrete
1013
{
@@ -32,32 +35,100 @@ namespace Rubberduck.Inspections.Concrete
3235
/// </example>
3336
public sealed class ObsoleteTypeHintInspection : InspectionBase
3437
{
38+
private readonly IDeclarationFinderProvider _declarationFinderProvider;
39+
3540
public ObsoleteTypeHintInspection(RubberduckParserState state)
36-
: base(state) { }
41+
: base(state)
42+
{
43+
_declarationFinderProvider = state;
44+
}
3745

3846
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3947
{
40-
var results = UserDeclarations.ToList();
41-
42-
var declarations = from item in results
43-
where item.HasTypeHint
44-
select
45-
new DeclarationInspectionResult(this,
46-
string.Format(InspectionResults.ObsoleteTypeHintInspection,
47-
InspectionsUI.Inspections_Declaration, item.DeclarationType.ToString().ToLower(),
48-
item.IdentifierName), item);
49-
50-
var references = from item in results.SelectMany(d => d.References)
51-
where item.HasTypeHint()
52-
select
53-
new IdentifierReferenceInspectionResult(this,
54-
string.Format(InspectionResults.ObsoleteTypeHintInspection,
55-
InspectionsUI.Inspections_Usage, item.Declaration.DeclarationType.ToString().ToLower(),
56-
item.IdentifierName),
57-
State,
58-
item);
59-
60-
return declarations.Union<IInspectionResult>(references);
48+
var finder = _declarationFinderProvider.DeclarationFinder;
49+
50+
var results = new List<IInspectionResult>();
51+
foreach (var moduleDeclaration in State.DeclarationFinder.UserDeclarations(DeclarationType.Module))
52+
{
53+
if (moduleDeclaration == null)
54+
{
55+
continue;
56+
}
57+
58+
var module = moduleDeclaration.QualifiedModuleName;
59+
results.AddRange(DoGetInspectionResults(module, finder));
60+
}
61+
62+
return results;
63+
}
64+
65+
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
66+
{
67+
var finder = _declarationFinderProvider.DeclarationFinder;
68+
return DoGetInspectionResults(module, finder);
69+
}
70+
71+
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
72+
{
73+
var declarationResults = DeclarationResults(module, finder);
74+
var referenceResults = ReferenceResults(module, finder);
75+
return declarationResults
76+
.Concat(referenceResults);
77+
}
78+
79+
private IEnumerable<IInspectionResult> DeclarationResults(QualifiedModuleName module, DeclarationFinder finder)
80+
{
81+
var objectionableDeclarations = finder.Members(module)
82+
.Where(declaration => declaration.HasTypeHint);
83+
return objectionableDeclarations.Select(InspectionResult);
84+
}
85+
86+
private IInspectionResult InspectionResult(Declaration declaration)
87+
{
88+
return new DeclarationInspectionResult(
89+
this,
90+
ResultDescription(declaration),
91+
declaration);
92+
}
93+
94+
private string ResultDescription(Declaration declaration)
95+
{
96+
var declarationTypeName = declaration.DeclarationType.ToString().ToLower();
97+
var identifierName = declaration.IdentifierName;
98+
return string.Format(
99+
InspectionResults.ObsoleteTypeHintInspection,
100+
InspectionsUI.Inspections_Declaration,
101+
declarationTypeName,
102+
identifierName);
103+
}
104+
105+
private IEnumerable<IInspectionResult> ReferenceResults(QualifiedModuleName module, DeclarationFinder finder)
106+
{
107+
var objectionableReferences = finder.IdentifierReferences(module)
108+
.Where(reference => reference?.Declaration != null
109+
&& reference.Declaration.IsUserDefined
110+
&& reference.HasTypeHint());
111+
return objectionableReferences
112+
.Select(reference => InspectionResult(reference, _declarationFinderProvider));
113+
}
114+
115+
private IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider)
116+
{
117+
return new IdentifierReferenceInspectionResult(
118+
this,
119+
ResultDescription(reference),
120+
declarationFinderProvider,
121+
reference);
122+
}
123+
124+
private string ResultDescription(IdentifierReference reference)
125+
{
126+
var declarationTypeName = reference.Declaration.DeclarationType.ToString().ToLower();
127+
var identifierName = reference.IdentifierName;
128+
return string.Format(InspectionResults.ObsoleteTypeHintInspection,
129+
InspectionsUI.Inspections_Usage,
130+
declarationTypeName,
131+
identifierName);
61132
}
62133
}
63134
}

0 commit comments

Comments
 (0)