Skip to content

Commit 6a17bf7

Browse files
committed
Make UnreachableCaseInspector.InspectForUnreachableCases pure
Also turns the inspector in UnreachableCaseInspection into a constructor injected field.
1 parent b26b8f4 commit 6a17bf7

File tree

9 files changed

+105
-252
lines changed

9 files changed

+105
-252
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection/UnreachableCaseInspection.cs

Lines changed: 10 additions & 83 deletions
Original file line numberDiff line numberDiff line change
@@ -115,7 +115,7 @@ namespace Rubberduck.Inspections.Concrete.UnreachableCaseInspection
115115
/// </example>
116116
public sealed class UnreachableCaseInspection : InspectionBase, IParseTreeInspection
117117
{
118-
private readonly IUnreachableCaseInspectorFactory _unreachableCaseInspectorFactory;
118+
private readonly IUnreachableCaseInspector _inspector;
119119
private readonly IParseTreeValueVisitor _parseTreeValueVisitor;
120120
private readonly IInspectionListener<VBAParser.SelectCaseStmtContext> _listener;
121121

@@ -128,10 +128,13 @@ public enum CaseInspectionResultType
128128
CaseElse
129129
}
130130

131-
public UnreachableCaseInspection(IDeclarationFinderProvider declarationFinderProvider, IUnreachableCaseInspectionFactoryProvider factoryProvider, IParseTreeValueVisitor parseTreeValueVisitor)
131+
public UnreachableCaseInspection(
132+
IDeclarationFinderProvider declarationFinderProvider,
133+
IUnreachableCaseInspector inspector,
134+
IParseTreeValueVisitor parseTreeValueVisitor)
132135
: base(declarationFinderProvider)
133136
{
134-
_unreachableCaseInspectorFactory = factoryProvider.CreateIUnreachableInspectorFactory();
137+
_inspector = inspector;
135138
_parseTreeValueVisitor = parseTreeValueVisitor;
136139
_listener = new UnreachableCaseInspectionListener();
137140
}
@@ -142,38 +145,30 @@ public UnreachableCaseInspection(IDeclarationFinderProvider declarationFinderPro
142145

143146
protected override IEnumerable<IInspectionResult> DoGetInspectionResults(DeclarationFinder finder)
144147
{
145-
var selectCaseInspector = _unreachableCaseInspectorFactory.Create(GetVariableTypeNameFunction(finder));
146-
147148
return finder.UserDeclarations(DeclarationType.Module)
148149
.Where(module => module != null)
149-
.SelectMany(module => DoGetInspectionResults(module.QualifiedModuleName, finder, selectCaseInspector))
150+
.SelectMany(module => DoGetInspectionResults(module.QualifiedModuleName, finder))
150151
.ToList();
151152
}
152153

153154
protected override IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
154-
{
155-
var selectCaseInspector = _unreachableCaseInspectorFactory.Create(GetVariableTypeNameFunction(finder));
156-
return DoGetInspectionResults(module, finder, selectCaseInspector);
157-
}
158-
159-
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder, IUnreachableCaseInspector selectCaseInspector)
160155
{
161156
var qualifiedSelectCaseStmts = _listener.Contexts(module)
162157
// ignore filtering here to make the search space smaller
163158
.Where(result => !result.IsIgnoringInspectionResultFor(finder, AnnotationName));
164159

165160
return qualifiedSelectCaseStmts
166-
.SelectMany(context => ResultsForContext(context, selectCaseInspector, finder))
161+
.SelectMany(context => ResultsForContext(context, finder))
167162
.ToList();
168163
}
169164

170-
private IEnumerable<IInspectionResult> ResultsForContext(QualifiedContext<VBAParser.SelectCaseStmtContext> qualifiedSelectCaseStmt, IUnreachableCaseInspector selectCaseInspector, DeclarationFinder finder)
165+
private IEnumerable<IInspectionResult> ResultsForContext(QualifiedContext<VBAParser.SelectCaseStmtContext> qualifiedSelectCaseStmt, DeclarationFinder finder)
171166
{
172167
var module = qualifiedSelectCaseStmt.ModuleName;
173168
var selectStmt = qualifiedSelectCaseStmt.Context;
174169
var contextValues = _parseTreeValueVisitor.VisitChildren(module, selectStmt, finder);
175170

176-
var results = selectCaseInspector.InspectForUnreachableCases(module, selectStmt, contextValues);
171+
var results = _inspector.InspectForUnreachableCases(module, selectStmt, contextValues, finder);
177172

178173
return results
179174
.Select(resultTpl => CreateInspectionResult(qualifiedSelectCaseStmt, resultTpl.context, resultTpl.resultType))
@@ -212,74 +207,6 @@ private IInspectionResult CreateInspectionResult(QualifiedContext<VBAParser.Sele
212207
new QualifiedContext<ParserRuleContext>(selectStmt.ModuleName, unreachableBlock));
213208
}
214209

215-
private Func<QualifiedModuleName, ParserRuleContext,(bool success, IdentifierReference reference)> GetIdentifierReferenceForContextFunction(DeclarationFinder finder)
216-
{
217-
return (module, context) => GetIdentifierReferenceForContext(module, context, finder);
218-
}
219-
220-
//public static to support tests
221-
//FIXME There should not be additional public methods just for tests. This class seems to want to be split or at least reorganized.
222-
public static (bool success, IdentifierReference idRef) GetIdentifierReferenceForContext(QualifiedModuleName module, ParserRuleContext context, DeclarationFinder finder)
223-
{
224-
if (context == null)
225-
{
226-
return (false, null);
227-
}
228-
229-
var qualifiedSelection = new QualifiedSelection(module, context.GetSelection());
230-
231-
var identifierReferences =
232-
finder
233-
.IdentifierReferences(qualifiedSelection)
234-
.Where(reference => reference.Context == context)
235-
.ToList();
236-
237-
return identifierReferences.Count == 1
238-
? (true, identifierReferences.First())
239-
: (false, null);
240-
}
241-
242-
private Func<string, QualifiedModuleName, ParserRuleContext, string> GetVariableTypeNameFunction(DeclarationFinder finder)
243-
{
244-
var referenceRetriever = GetIdentifierReferenceForContextFunction(finder);
245-
return (variableName, module, ancestor) => GetVariableTypeName(module, variableName, ancestor, referenceRetriever);
246-
}
247-
248-
private string GetVariableTypeName(QualifiedModuleName module, string variableName, ParserRuleContext ancestor, Func<QualifiedModuleName, ParserRuleContext, (bool success, IdentifierReference reference)> referenceRetriever)
249-
{
250-
if (ancestor == null)
251-
{
252-
return string.Empty;
253-
}
254-
255-
var descendents = ancestor.GetDescendents<VBAParser.SimpleNameExprContext>()
256-
.Where(desc => desc.GetText().Equals(variableName))
257-
.ToList();
258-
if (!descendents.Any())
259-
{
260-
return string.Empty;
261-
}
262-
263-
var firstDescendent = descendents.First();
264-
var (success, reference) = referenceRetriever(module, firstDescendent);
265-
return success ?
266-
GetBaseTypeForDeclaration(reference.Declaration)
267-
: string.Empty;
268-
}
269-
270-
private string GetBaseTypeForDeclaration(Declaration declaration)
271-
{
272-
var localDeclaration = declaration;
273-
var iterationGuard = 0;
274-
while (!(localDeclaration is null)
275-
&& !localDeclaration.AsTypeIsBaseType
276-
&& iterationGuard++ < 5)
277-
{
278-
localDeclaration = localDeclaration.AsTypeDeclaration;
279-
}
280-
return localDeclaration is null ? declaration.AsTypeName : localDeclaration.AsTypeName;
281-
}
282-
283210
private class UnreachableCaseInspectionListener : InspectionListenerBase<VBAParser.SelectCaseStmtContext>
284211
{
285212
public override void EnterSelectCaseStmt([NotNull] VBAParser.SelectCaseStmtContext context)

Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection/UnreachableCaseInspectionFactoryProvider.cs

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

Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection/UnreachableCaseInspector.cs

Lines changed: 65 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,8 @@
44
using System;
55
using System.Collections.Generic;
66
using System.Linq;
7+
using Rubberduck.Parsing.Symbols;
8+
using Rubberduck.Parsing.VBA.DeclarationCaching;
79
using Rubberduck.VBEditor;
810

911
namespace Rubberduck.Inspections.Concrete.UnreachableCaseInspection
@@ -13,7 +15,8 @@ public interface IUnreachableCaseInspector
1315
ICollection<(UnreachableCaseInspection.CaseInspectionResultType resultType, ParserRuleContext context)> InspectForUnreachableCases(
1416
QualifiedModuleName module,
1517
VBAParser.SelectCaseStmtContext selectCaseContext,
16-
IParseTreeVisitorResults parseTreeValues);
18+
IParseTreeVisitorResults parseTreeValues,
19+
DeclarationFinder finder);
1720
string SelectExpressionTypeName(
1821
VBAParser.SelectCaseStmtContext selectCaseContext,
1922
IParseTreeVisitorResults parseTreeValues);
@@ -22,20 +25,18 @@ string SelectExpressionTypeName(
2225
public class UnreachableCaseInspector : IUnreachableCaseInspector
2326
{
2427
private readonly IParseTreeValueFactory _valueFactory;
25-
private readonly Func<string, QualifiedModuleName, ParserRuleContext, string> _getVariableDeclarationTypeName;
2628

2729
public UnreachableCaseInspector(
28-
IParseTreeValueFactory valueFactory,
29-
Func<string, QualifiedModuleName, ParserRuleContext, string> getVariableTypeName = null)
30+
IParseTreeValueFactory valueFactory)
3031
{
3132
_valueFactory = valueFactory;
32-
_getVariableDeclarationTypeName = getVariableTypeName;
3333
}
3434

3535
public ICollection<(UnreachableCaseInspection.CaseInspectionResultType resultType, ParserRuleContext context)> InspectForUnreachableCases(
3636
QualifiedModuleName module,
3737
VBAParser.SelectCaseStmtContext selectCaseContext,
38-
IParseTreeVisitorResults parseTreeValues)
38+
IParseTreeVisitorResults parseTreeValues,
39+
DeclarationFinder finder)
3940
{
4041
var (selectExpressionTypeName, selectExpressionValue) = SelectExpressionTypeNameAndValue(selectCaseContext, parseTreeValues);
4142

@@ -61,7 +62,7 @@ public UnreachableCaseInspector(
6162
.Select(tpl => tpl.caseClause)
6263
.ToList();
6364

64-
var rangeClauseFilter = BuildRangeClauseFilter(module, remainingCasesToInspect, selectExpressionTypeName, parseTreeValues);
65+
var rangeClauseFilter = BuildRangeClauseFilter(module, remainingCasesToInspect, selectExpressionTypeName, parseTreeValues, finder);
6566
if (!(selectExpressionValue is null) && selectExpressionValue.ParsesToConstantValue)
6667
{
6768
rangeClauseFilter.SelectExpressionValue = selectExpressionValue;
@@ -146,29 +147,79 @@ public UnreachableCaseInspector(
146147
return null;
147148
}
148149

149-
private IExpressionFilter BuildRangeClauseFilter(QualifiedModuleName module, IEnumerable<VBAParser.CaseClauseContext> caseClauses, string selectExpressionTypeName, IParseTreeVisitorResults parseTreeValues)
150+
private IExpressionFilter BuildRangeClauseFilter(QualifiedModuleName module, IEnumerable<VBAParser.CaseClauseContext> caseClauses, string selectExpressionTypeName, IParseTreeVisitorResults parseTreeValues, DeclarationFinder finder)
150151
{
151152
var rangeClauseFilter = ExpressionFilterFactory.Create(selectExpressionTypeName);
152153

153-
if (_getVariableDeclarationTypeName is null)
154-
{
155-
return rangeClauseFilter;
156-
}
157-
158154
var rangeClauses = caseClauses.SelectMany(caseClause => caseClause.rangeClause());
159155
foreach (var rangeClause in rangeClauses)
160156
{
161157
var expression = GetRangeClauseExpression(rangeClause, parseTreeValues);
162158
if (!expression?.LHS?.ParsesToConstantValue ?? false)
163159
{
164-
var typeName = _getVariableDeclarationTypeName(expression.LHS.Token, module, rangeClause);
160+
var typeName = GetVariableTypeName(module, expression.LHS.Token, rangeClause, finder);
165161
rangeClauseFilter.AddComparablePredicateFilter(expression.LHS.Token, typeName);
166162
}
167163
}
168164

169165
return rangeClauseFilter;
170166
}
171167

168+
private string GetVariableTypeName(QualifiedModuleName module, string variableName, ParserRuleContext ancestor, DeclarationFinder finder)
169+
{
170+
if (ancestor == null)
171+
{
172+
return string.Empty;
173+
}
174+
175+
var descendents = ancestor.GetDescendents<VBAParser.SimpleNameExprContext>()
176+
.Where(desc => desc.GetText().Equals(variableName))
177+
.ToList();
178+
if (!descendents.Any())
179+
{
180+
return string.Empty;
181+
}
182+
183+
var firstDescendent = descendents.First();
184+
var (success, reference) = GetIdentifierReferenceForContext(module, firstDescendent, finder);
185+
return success ?
186+
GetBaseTypeForDeclaration(reference.Declaration)
187+
: string.Empty;
188+
}
189+
190+
private static (bool success, IdentifierReference idRef) GetIdentifierReferenceForContext(QualifiedModuleName module, ParserRuleContext context, DeclarationFinder finder)
191+
{
192+
if (context == null)
193+
{
194+
return (false, null);
195+
}
196+
197+
var qualifiedSelection = new QualifiedSelection(module, context.GetSelection());
198+
199+
var identifierReferences =
200+
finder
201+
.IdentifierReferences(qualifiedSelection)
202+
.Where(reference => reference.Context == context)
203+
.ToList();
204+
205+
return identifierReferences.Count == 1
206+
? (true, identifierReferences.First())
207+
: (false, null);
208+
}
209+
210+
private string GetBaseTypeForDeclaration(Declaration declaration)
211+
{
212+
var localDeclaration = declaration;
213+
var iterationGuard = 0;
214+
while (!(localDeclaration is null)
215+
&& !localDeclaration.AsTypeIsBaseType
216+
&& iterationGuard++ < 5)
217+
{
218+
localDeclaration = localDeclaration.AsTypeDeclaration;
219+
}
220+
return localDeclaration is null ? declaration.AsTypeName : localDeclaration.AsTypeName;
221+
}
222+
172223
public string SelectExpressionTypeName(
173224
VBAParser.SelectCaseStmtContext selectStmt,
174225
IParseTreeVisitorResults parseTreeValues)

Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection/UnreachableCaseInspectorFactory.cs

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

Rubberduck.Main/Root/RubberduckIoCInstaller.cs

Lines changed: 0 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -382,12 +382,6 @@ private void RegisterUnreachableCaseFactories(IWindsorContainer container)
382382
container.Register(Component.For<IParseTreeValueFactory>()
383383
.ImplementedBy<ParseTreeValueFactory>()
384384
.LifestyleSingleton());
385-
container.Register(Component.For<IUnreachableCaseInspectorFactory>()
386-
.ImplementedBy<UnreachableCaseInspectorFactory>()
387-
.LifestyleSingleton());
388-
container.Register(Component.For<IUnreachableCaseInspectionFactoryProvider>()
389-
.ImplementedBy<UnreachableCaseInspectionFactoryProvider>()
390-
.LifestyleSingleton());
391385
}
392386

393387

RubberduckTests/Inspections/UnreachableCase/ExpressionFilterUnitTests.cs

Lines changed: 2 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -39,32 +39,8 @@ public class ExpressionFilterUnitTests
3939
private const string CLAUSETYPE_VALUE_DELIMITER = "!";
4040
private const string RANGE_STARTEND_DELIMITER = ":";
4141

42-
private IUnreachableCaseInspectionFactoryProvider _factoryProvider;
43-
private IParseTreeValueFactory _valueFactory;
44-
45-
private IUnreachableCaseInspectionFactoryProvider FactoryProvider
46-
{
47-
get
48-
{
49-
if (_factoryProvider is null)
50-
{
51-
_factoryProvider = new UnreachableCaseInspectionFactoryProvider();
52-
}
53-
return _factoryProvider;
54-
}
55-
}
56-
57-
private IParseTreeValueFactory ValueFactory
58-
{
59-
get
60-
{
61-
if (_valueFactory is null)
62-
{
63-
_valueFactory = FactoryProvider.CreateIParseTreeValueFactory();
64-
}
65-
return _valueFactory;
66-
}
67-
}
42+
private readonly Lazy<IParseTreeValueFactory> _valueFactory = new Lazy<IParseTreeValueFactory>(() => new ParseTreeValueFactory());
43+
private IParseTreeValueFactory ValueFactory => _valueFactory.Value;
6844

6945
[TestCase("Min!-5000", "", "Min(-5000)Max(typeMax)")]
7046
[TestCase("Min!-5000,Max!5000", "", "Min(-5000)Max(5000)")]

0 commit comments

Comments
 (0)