Skip to content

Commit 96e159d

Browse files
committed
Extract IdentifierReferenceInspectionBase
1 parent b267817 commit 96e159d

File tree

5 files changed

+96
-126
lines changed

5 files changed

+96
-126
lines changed
Lines changed: 66 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,66 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Inspections.Extensions;
4+
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing.Inspections.Abstract;
6+
using Rubberduck.Parsing.Symbols;
7+
using Rubberduck.Parsing.VBA;
8+
using Rubberduck.VBEditor;
9+
10+
namespace Rubberduck.Inspections.Abstract
11+
{
12+
public abstract class IdentifierReferenceInspectionBase : InspectionBase
13+
{
14+
protected readonly IDeclarationFinderProvider DeclarationFinderProvider;
15+
16+
public IdentifierReferenceInspectionBase(RubberduckParserState state)
17+
: base(state)
18+
{
19+
DeclarationFinderProvider = state;
20+
}
21+
22+
protected abstract bool IsResultReference(IdentifierReference reference);
23+
protected abstract string ResultDescription(IdentifierReference reference);
24+
25+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
26+
{
27+
var results = new List<IInspectionResult>();
28+
foreach (var moduleDeclaration in State.DeclarationFinder.UserDeclarations(DeclarationType.Module))
29+
{
30+
if (moduleDeclaration == null || moduleDeclaration.IsIgnoringInspectionResultFor(AnnotationName))
31+
{
32+
continue;
33+
}
34+
35+
var module = moduleDeclaration.QualifiedModuleName;
36+
results.AddRange(DoGetInspectionResults(module));
37+
}
38+
39+
return results;
40+
}
41+
42+
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
43+
{
44+
var objectionableReferences = ReferencesInModule(module)
45+
.Where(IsResultReference);
46+
47+
return objectionableReferences
48+
.Select(reference => InspectionResult(reference, DeclarationFinderProvider))
49+
.ToList();
50+
}
51+
52+
protected virtual IEnumerable<IdentifierReference> ReferencesInModule(QualifiedModuleName module)
53+
{
54+
return DeclarationFinderProvider.DeclarationFinder.IdentifierReferences(module);
55+
}
56+
57+
protected virtual IInspectionResult InspectionResult(IdentifierReference reference, IDeclarationFinderProvider declarationFinderProvider)
58+
{
59+
return new IdentifierReferenceInspectionResult(
60+
this,
61+
ResultDescription(reference),
62+
declarationFinderProvider,
63+
reference);
64+
}
65+
}
66+
}

Rubberduck.CodeAnalysis/Inspections/Concrete/DefaultMemberRequiredInspection.cs

Lines changed: 7 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,11 @@
11
using System.Collections.Generic;
2-
using System.Linq;
32
using Rubberduck.Inspections.Abstract;
43
using Rubberduck.Inspections.Inspections.Extensions;
5-
using Rubberduck.Inspections.Results;
64
using Rubberduck.Parsing.Inspections;
7-
using Rubberduck.Parsing.Inspections.Abstract;
85
using Rubberduck.Parsing.Symbols;
96
using Rubberduck.Parsing.VBA;
107
using Rubberduck.Resources.Inspections;
8+
using Rubberduck.VBEditor;
119

1210
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
1311
{
@@ -55,43 +53,26 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
5553
/// End Sub
5654
/// ]]>
5755
/// </example>
58-
public class DefaultMemberRequiredInspection : InspectionBase
56+
public class DefaultMemberRequiredInspection : IdentifierReferenceInspectionBase
5957
{
60-
private readonly IDeclarationFinderProvider _declarationFinderProvider;
61-
6258
public DefaultMemberRequiredInspection(RubberduckParserState state)
6359
: base(state)
6460
{
65-
_declarationFinderProvider = state;
66-
6761
//This will most likely cause a runtime error. The exceptions are rare and should be refactored or made explicit with an @Ignore annotation.
6862
Severity = CodeInspectionSeverity.Error;
6963
}
7064

71-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
72-
{
73-
var finder = _declarationFinderProvider.DeclarationFinder;
74-
75-
var failedIndexedDefaultMemberAccesses = finder.FailedIndexedDefaultMemberAccesses();
76-
return failedIndexedDefaultMemberAccesses
77-
.Where(failedIndexedDefaultMemberAccess => !IsIgnored(failedIndexedDefaultMemberAccess))
78-
.Select(failedIndexedDefaultMemberAccess => InspectionResult(failedIndexedDefaultMemberAccess, _declarationFinderProvider));
79-
}
80-
81-
private bool IsIgnored(IdentifierReference assignment)
65+
protected override IEnumerable<IdentifierReference> ReferencesInModule(QualifiedModuleName module)
8266
{
83-
return assignment.IsIgnoringInspectionResultFor(AnnotationName);
67+
return DeclarationFinderProvider.DeclarationFinder.FailedIndexedDefaultMemberAccesses(module);
8468
}
8569

86-
private IInspectionResult InspectionResult(IdentifierReference failedCoercion, IDeclarationFinderProvider declarationFinderProvider)
70+
protected override bool IsResultReference(IdentifierReference failedIndexedDefaultMemberAccess)
8771
{
88-
return new IdentifierReferenceInspectionResult(this,
89-
ResultDescription(failedCoercion),
90-
declarationFinderProvider,
91-
failedCoercion);
72+
return !failedIndexedDefaultMemberAccess.IsIgnoringInspectionResultFor(AnnotationName);
9273
}
9374

94-
private string ResultDescription(IdentifierReference failedIndexedDefaultMemberAccess)
75+
protected override string ResultDescription(IdentifierReference failedIndexedDefaultMemberAccess)
9576
{
9677
var expression = failedIndexedDefaultMemberAccess.IdentifierName;
9778
var typeName = failedIndexedDefaultMemberAccess.Declaration?.FullAsTypeName;

Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureRequiredInspection.cs

Lines changed: 7 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,11 @@
11
using System.Collections.Generic;
2-
using System.Linq;
32
using Rubberduck.Inspections.Abstract;
43
using Rubberduck.Inspections.Inspections.Extensions;
5-
using Rubberduck.Inspections.Results;
64
using Rubberduck.Parsing.Inspections;
7-
using Rubberduck.Parsing.Inspections.Abstract;
85
using Rubberduck.Parsing.Symbols;
96
using Rubberduck.Parsing.VBA;
107
using Rubberduck.Resources.Inspections;
8+
using Rubberduck.VBEditor;
119

1210
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
1311
{
@@ -53,43 +51,26 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
5351
/// End Sub
5452
/// ]]>
5553
/// </example>
56-
public class ProcedureRequiredInspection : InspectionBase
54+
public class ProcedureRequiredInspection : IdentifierReferenceInspectionBase
5755
{
58-
private readonly IDeclarationFinderProvider _declarationFinderProvider;
59-
6056
public ProcedureRequiredInspection(RubberduckParserState state)
6157
: base(state)
6258
{
63-
_declarationFinderProvider = state;
64-
6559
//This will most likely cause a runtime error. The exceptions are rare and should be refactored or made explicit with an @Ignore annotation.
6660
Severity = CodeInspectionSeverity.Error;
6761
}
6862

69-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
70-
{
71-
var finder = _declarationFinderProvider.DeclarationFinder;
72-
73-
var failedProcedureCoercions = finder.FailedProcedureCoercions();
74-
return failedProcedureCoercions
75-
.Where(failedCoercion => !IsIgnored(failedCoercion))
76-
.Select(failedCoercion => InspectionResult(failedCoercion, _declarationFinderProvider));
77-
}
78-
79-
private bool IsIgnored(IdentifierReference assignment)
63+
protected override IEnumerable<IdentifierReference> ReferencesInModule(QualifiedModuleName module)
8064
{
81-
return assignment.IsIgnoringInspectionResultFor(AnnotationName);
65+
return DeclarationFinderProvider.DeclarationFinder.FailedProcedureCoercions(module);
8266
}
8367

84-
private IInspectionResult InspectionResult(IdentifierReference failedCoercion, IDeclarationFinderProvider declarationFinderProvider)
68+
protected override bool IsResultReference(IdentifierReference failedCoercion)
8569
{
86-
return new IdentifierReferenceInspectionResult(this,
87-
ResultDescription(failedCoercion),
88-
declarationFinderProvider,
89-
failedCoercion);
70+
return !failedCoercion.IsIgnoringInspectionResultFor(AnnotationName);
9071
}
9172

92-
private string ResultDescription(IdentifierReference failedCoercion)
73+
protected override string ResultDescription(IdentifierReference failedCoercion)
9374
{
9475
var expression = failedCoercion.IdentifierName;
9576
var typeName = failedCoercion.Declaration?.FullAsTypeName;

Rubberduck.CodeAnalysis/Inspections/Concrete/UseOfBangNotationInspection.cs

Lines changed: 8 additions & 45 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,10 @@
1-
using System.Collections.Generic;
2-
using System.Linq;
3-
using Rubberduck.Inspections.Abstract;
4-
using Rubberduck.Inspections.Results;
5-
using Rubberduck.Parsing.Inspections.Abstract;
1+
using Rubberduck.Inspections.Abstract;
62
using Rubberduck.Resources.Inspections;
73
using Rubberduck.Parsing.Symbols;
84
using Rubberduck.Parsing.VBA;
95
using Rubberduck.Inspections.Inspections.Extensions;
106
using Rubberduck.Parsing.Grammar;
11-
using Rubberduck.VBEditor;
7+
using Rubberduck.Parsing.Inspections;
128

139
namespace Rubberduck.Inspections.Concrete
1410
{
@@ -57,58 +53,25 @@ namespace Rubberduck.Inspections.Concrete
5753
/// End Sub
5854
/// ]]>
5955
/// </example>
60-
public sealed class UseOfBangNotationInspection : InspectionBase
56+
public sealed class UseOfBangNotationInspection : IdentifierReferenceInspectionBase
6157
{
6258
public UseOfBangNotationInspection(RubberduckParserState state)
63-
: base(state) { }
64-
65-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
66-
{
67-
var results = new List<IInspectionResult>();
68-
foreach (var moduleDeclaration in State.DeclarationFinder.UserDeclarations(DeclarationType.Module))
69-
{
70-
if (moduleDeclaration == null || moduleDeclaration.IsIgnoringInspectionResultFor(AnnotationName))
71-
{
72-
continue;
73-
}
74-
75-
var module = moduleDeclaration.QualifiedModuleName;
76-
results.AddRange(DoGetInspectionResults(module));
77-
}
78-
79-
return results;
80-
}
81-
82-
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
59+
: base(state)
8360
{
84-
var usesOfBang = State.DeclarationFinder
85-
.IdentifierReferences(module)
86-
.Where(IsRelevantReference);
87-
88-
return usesOfBang
89-
.Select(useOfBang => InspectionResult(useOfBang, State))
90-
.ToList();
61+
Severity = CodeInspectionSeverity.Suggestion;
9162
}
9263

93-
private bool IsRelevantReference(IdentifierReference reference)
64+
protected override bool IsResultReference(IdentifierReference reference)
9465
{
9566
return reference.IsIndexedDefaultMemberAccess
9667
&& reference.DefaultMemberRecursionDepth == 1
9768
&& reference.Context is VBAParser.DictionaryAccessContext
9869
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
9970
}
10071

101-
private IInspectionResult InspectionResult(IdentifierReference dictionaryAccess, IDeclarationFinderProvider declarationFinderProvider)
102-
{
103-
return new IdentifierReferenceInspectionResult(this,
104-
ResultDescription(dictionaryAccess),
105-
declarationFinderProvider,
106-
dictionaryAccess);
107-
}
108-
109-
private string ResultDescription(IdentifierReference dictionaryAccess)
72+
protected override string ResultDescription(IdentifierReference reference)
11073
{
111-
var expression = dictionaryAccess.IdentifierName;
74+
var expression = reference.IdentifierName;
11275
return string.Format(InspectionResults.UseOfBangNotationInspection, expression);
11376
}
11477
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ValueRequiredInspection.cs

Lines changed: 8 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,11 @@
11
using System.Collections.Generic;
2-
using System.Linq;
32
using Rubberduck.Inspections.Abstract;
43
using Rubberduck.Inspections.Inspections.Extensions;
5-
using Rubberduck.Inspections.Results;
64
using Rubberduck.Parsing.Inspections;
7-
using Rubberduck.Parsing.Inspections.Abstract;
85
using Rubberduck.Parsing.Symbols;
96
using Rubberduck.Parsing.VBA;
107
using Rubberduck.Resources.Inspections;
8+
using Rubberduck.VBEditor;
119

1210
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
1311
{
@@ -57,46 +55,27 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
5755
/// End Sub
5856
/// ]]>
5957
/// </example>
60-
public class ValueRequiredInspection : InspectionBase
58+
public class ValueRequiredInspection : IdentifierReferenceInspectionBase
6159
{
62-
private readonly IDeclarationFinderProvider _declarationFinderProvider;
63-
6460
public ValueRequiredInspection(RubberduckParserState state)
6561
: base(state)
6662
{
67-
_declarationFinderProvider = state;
68-
6963
//This will most likely cause a runtime error. The exceptions are rare and should be refactored or made explicit with an @Ignore annotation.
7064
Severity = CodeInspectionSeverity.Error;
7165
}
7266

73-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
74-
{
75-
var finder = _declarationFinderProvider.DeclarationFinder;
76-
77-
//Assignments are already covered by the ObjectVariableNotSetInspection.
78-
var failedLetCoercionAccesses = finder.FailedLetCoercions()
79-
.Where(failedLetCoercion => !failedLetCoercion.IsAssignment);
80-
81-
return failedLetCoercionAccesses
82-
.Where(failedLetCoercion => !IsIgnored(failedLetCoercion))
83-
.Select(failedLetCoercion => InspectionResult(failedLetCoercion, _declarationFinderProvider));
84-
}
85-
86-
private bool IsIgnored(IdentifierReference assignment)
67+
protected override IEnumerable<IdentifierReference> ReferencesInModule(QualifiedModuleName module)
8768
{
88-
return assignment.IsIgnoringInspectionResultFor(AnnotationName);
69+
return DeclarationFinderProvider.DeclarationFinder.FailedLetCoercions(module);
8970
}
9071

91-
private IInspectionResult InspectionResult(IdentifierReference failedLetCoercion, IDeclarationFinderProvider declarationFinderProvider)
72+
protected override bool IsResultReference(IdentifierReference failedLetCoercion)
9273
{
93-
return new IdentifierReferenceInspectionResult(this,
94-
ResultDescription(failedLetCoercion),
95-
declarationFinderProvider,
96-
failedLetCoercion);
74+
return !failedLetCoercion.IsAssignment
75+
&& !failedLetCoercion.IsIgnoringInspectionResultFor(AnnotationName);
9776
}
9877

99-
private string ResultDescription(IdentifierReference failedLetCoercion)
78+
protected override string ResultDescription(IdentifierReference failedLetCoercion)
10079
{
10180
var expression = failedLetCoercion.IdentifierName;
10281
var typeName = failedLetCoercion.Declaration?.FullAsTypeName;

0 commit comments

Comments
 (0)