Skip to content

Commit 33103b5

Browse files
committed
Fix UnassignedVariableUsageInspection
Further non-assignment accesses after an assignment via a by ref argument also triggered results. Moreover bracket expressions now have the QMN of the containing module. Furthermore, many declaration inspections have been converted to use the base classes.
1 parent a1b4ee7 commit 33103b5

22 files changed

+430
-280
lines changed

Rubberduck.CodeAnalysis/Inspections/Abstract/ImplicitTypeInspectionBase.cs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,8 +7,12 @@ namespace Rubberduck.Inspections.Abstract
77
public abstract class ImplicitTypeInspectionBase : DeclarationInspectionBase
88
{
99
protected ImplicitTypeInspectionBase(RubberduckParserState state, params DeclarationType[] relevantDeclarationTypes)
10-
:base(state, relevantDeclarationTypes)
11-
{ }
10+
: base(state, relevantDeclarationTypes)
11+
{}
12+
13+
protected ImplicitTypeInspectionBase(RubberduckParserState state, DeclarationType[] relevantDeclarationTypes, DeclarationType[] excludeDeclarationTypes)
14+
: base(state, relevantDeclarationTypes, excludeDeclarationTypes)
15+
{}
1216

1317
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
1418
{

Rubberduck.CodeAnalysis/Inspections/Concrete/AssignedByValParameterInspection.cs

Lines changed: 14 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,9 @@
1-
using System.Collections.Generic;
21
using System.Linq;
32
using Rubberduck.Inspections.Abstract;
4-
using Rubberduck.Inspections.Results;
5-
using Rubberduck.Parsing.Inspections.Abstract;
63
using Rubberduck.Resources.Inspections;
74
using Rubberduck.Parsing.Symbols;
85
using Rubberduck.Parsing.VBA;
9-
using Rubberduck.Inspections.Inspections.Extensions;
6+
using Rubberduck.Parsing.VBA.DeclarationCaching;
107

118
namespace Rubberduck.Inspections.Concrete
129
{
@@ -36,23 +33,23 @@ namespace Rubberduck.Inspections.Concrete
3633
/// End Sub
3734
/// ]]>
3835
/// </example>
39-
public sealed class AssignedByValParameterInspection : InspectionBase
36+
public sealed class AssignedByValParameterInspection : DeclarationInspectionBase
4037
{
4138
public AssignedByValParameterInspection(RubberduckParserState state)
42-
: base(state)
43-
{ }
44-
45-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
39+
: base(state, DeclarationType.Parameter)
40+
{}
41+
42+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
4643
{
47-
var parameters = State.DeclarationFinder.UserDeclarations(DeclarationType.Parameter)
48-
.Cast<ParameterDeclaration>()
49-
.Where(item => !item.IsByRef
50-
&& item.References.Any(reference => reference.IsAssignment));
44+
return declaration is ParameterDeclaration parameter
45+
&& !parameter.IsByRef
46+
&& parameter.References
47+
.Any(reference => reference.IsAssignment);
48+
}
5149

52-
return parameters
53-
.Select(param => new DeclarationInspectionResult(this,
54-
string.Format(InspectionResults.AssignedByValParameterInspection, param.IdentifierName),
55-
param));
50+
protected override string ResultDescription(Declaration declaration)
51+
{
52+
return string.Format(InspectionResults.AssignedByValParameterInspection, declaration.IdentifierName);
5653
}
5754
}
5855
}
Lines changed: 28 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,10 @@
11
using System.Collections.Generic;
2-
using System.Linq;
32
using Rubberduck.Inspections.Abstract;
4-
using Rubberduck.Inspections.Results;
53
using Rubberduck.Parsing.Inspections;
64
using Rubberduck.Parsing.Inspections.Abstract;
75
using Rubberduck.Parsing.Symbols;
86
using Rubberduck.Parsing.VBA;
7+
using Rubberduck.Parsing.VBA.DeclarationCaching;
98

109
namespace Rubberduck.Inspections.Concrete
1110
{
@@ -16,20 +15,39 @@ namespace Rubberduck.Inspections.Concrete
1615
/// VBA projects should be meaningfully named, to avoid namespace clashes when referencing other VBA projects.
1716
/// </why>
1817
[CannotAnnotate]
19-
public sealed class DefaultProjectNameInspection : InspectionBase
18+
public sealed class DefaultProjectNameInspection : DeclarationInspectionBase
2019
{
2120
public DefaultProjectNameInspection(RubberduckParserState state)
22-
: base(state) { }
21+
: base(state, DeclarationType.Project)
22+
{}
2323

2424
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2525
{
26-
var projects = State.DeclarationFinder.UserDeclarations(DeclarationType.Project)
27-
.Where(item => item.IdentifierName.StartsWith("VBAProject"))
28-
.ToList();
26+
var finder = DeclarationFinderProvider.DeclarationFinder;
2927

30-
return projects
31-
.Select(issue => new DeclarationInspectionResult(this, Description, issue))
32-
.ToList();
28+
var results = new List<IInspectionResult>();
29+
foreach (var projectDeclaration in State.DeclarationFinder.UserDeclarations(DeclarationType.Project))
30+
{
31+
if (projectDeclaration == null)
32+
{
33+
continue;
34+
}
35+
36+
var module = projectDeclaration.QualifiedModuleName;
37+
results.AddRange(DoGetInspectionResults(module, finder));
38+
}
39+
40+
return results;
41+
}
42+
43+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
44+
{
45+
return declaration.IdentifierName.StartsWith("VBAProject");
46+
}
47+
48+
protected override string ResultDescription(Declaration declaration)
49+
{
50+
return Description;
3351
}
3452
}
3553
}

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyMethodInspection.cs

Lines changed: 8 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -1,16 +1,9 @@
11
using Rubberduck.Inspections.Abstract;
2-
using Rubberduck.Inspections.Results;
3-
using Rubberduck.Parsing.Inspections.Abstract;
42
using Rubberduck.Resources.Inspections;
53
using Rubberduck.Parsing.VBA;
6-
using System.Collections.Generic;
7-
using System.Linq;
84
using Rubberduck.Parsing.Symbols;
9-
using Rubberduck.Common;
105
using Rubberduck.Inspections.Inspections.Extensions;
11-
using Rubberduck.JunkDrawer.Extensions;
126
using Rubberduck.Parsing.VBA.DeclarationCaching;
13-
using Rubberduck.VBEditor;
147

158
namespace Rubberduck.Inspections.Concrete
169
{
@@ -35,47 +28,20 @@ namespace Rubberduck.Inspections.Concrete
3528
/// End Sub
3629
/// ]]>
3730
/// </example>
38-
internal class EmptyMethodInspection : InspectionBase
31+
internal class EmptyMethodInspection : DeclarationInspectionBase
3932
{
4033
public EmptyMethodInspection(RubberduckParserState state)
41-
: base(state) { }
34+
: base(state, DeclarationType.Member)
35+
{}
4236

43-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
37+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
4438
{
45-
var finder = State.DeclarationFinder;
46-
47-
var userInterfaces = UserInterfaces(finder);
48-
var emptyMethods = EmptyNonInterfaceMethods(finder, userInterfaces);
49-
50-
return emptyMethods.Select(Result);
51-
}
52-
53-
private static ICollection<QualifiedModuleName> UserInterfaces(DeclarationFinder finder)
54-
{
55-
return finder
56-
.FindAllUserInterfaces()
57-
.Select(decl => decl.QualifiedModuleName)
58-
.ToHashSet();
59-
}
60-
61-
private static IEnumerable<Declaration> EmptyNonInterfaceMethods(DeclarationFinder finder, ICollection<QualifiedModuleName> userInterfaces)
62-
{
63-
return finder
64-
.UserDeclarations(DeclarationType.Member)
65-
.Where(member => !userInterfaces.Contains(member.QualifiedModuleName)
66-
&& member is ModuleBodyElementDeclaration moduleBodyElement
67-
&& !moduleBodyElement.Block.ContainsExecutableStatements());
68-
}
69-
70-
private IInspectionResult Result(Declaration member)
71-
{
72-
return new DeclarationInspectionResult(
73-
this,
74-
ResultDescription(member),
75-
member);
39+
return declaration is ModuleBodyElementDeclaration member
40+
&& !member.IsInterfaceMember
41+
&& !member.Block.ContainsExecutableStatements();
7642
}
7743

78-
private static string ResultDescription(Declaration member)
44+
protected override string ResultDescription(Declaration member)
7945
{
8046
var identifierName = member.IdentifierName;
8147
var declarationType = member.DeclarationType.ToLocalizedString();
Lines changed: 14 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,8 @@
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;
9-
using Rubberduck.Inspections.Inspections.Extensions;
5+
using Rubberduck.Parsing.VBA.DeclarationCaching;
106

117
namespace Rubberduck.Inspections.Concrete
128
{
@@ -31,25 +27,23 @@ namespace Rubberduck.Inspections.Concrete
3127
/// End Property
3228
/// ]]>
3329
/// </example>
34-
public sealed class EncapsulatePublicFieldInspection : InspectionBase
30+
public sealed class EncapsulatePublicFieldInspection : DeclarationInspectionBase
3531
{
3632
public EncapsulatePublicFieldInspection(RubberduckParserState state)
37-
: base(state) { }
33+
: base(state, DeclarationType.Variable)
34+
{}
3835

39-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
36+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
4037
{
41-
// we're creating a public field for every control on a form, needs to be ignored.
42-
var fields = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
43-
.Where(item => item.DeclarationType != DeclarationType.Control
44-
&& (item.Accessibility == Accessibility.Public ||
45-
item.Accessibility == Accessibility.Global))
46-
.ToList();
38+
// we're creating a public field for every control on a form, needs to be ignored
39+
return declaration.DeclarationType != DeclarationType.Control
40+
&& (declaration.Accessibility == Accessibility.Public
41+
|| declaration.Accessibility == Accessibility.Global);
42+
}
4743

48-
return fields
49-
.Select(issue => new DeclarationInspectionResult(this,
50-
string.Format(InspectionResults.EncapsulatePublicFieldInspection, issue.IdentifierName),
51-
issue))
52-
.ToList();
44+
protected override string ResultDescription(Declaration declaration)
45+
{
46+
return string.Format(InspectionResults.EncapsulatePublicFieldInspection, declaration.IdentifierName);
5347
}
5448
}
5549
}

Rubberduck.CodeAnalysis/Inspections/Concrete/HostSpecificExpressionInspection.cs

Lines changed: 11 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,11 @@
11
using System.Collections.Generic;
22
using System.Linq;
33
using Rubberduck.Inspections.Abstract;
4-
using Rubberduck.Inspections.Results;
54
using Rubberduck.Parsing.Inspections.Abstract;
65
using Rubberduck.Resources.Inspections;
76
using Rubberduck.Parsing.Symbols;
87
using Rubberduck.Parsing.VBA;
8+
using Rubberduck.Parsing.VBA.DeclarationCaching;
99

1010
namespace Rubberduck.Inspections.Concrete
1111
{
@@ -30,15 +30,20 @@ namespace Rubberduck.Inspections.Concrete
3030
/// End Sub
3131
/// ]]>
3232
/// </example>
33-
public sealed class HostSpecificExpressionInspection : InspectionBase
33+
public sealed class HostSpecificExpressionInspection : DeclarationInspectionBase
3434
{
3535
public HostSpecificExpressionInspection(RubberduckParserState state)
36-
: base(state) { }
36+
: base(state, DeclarationType.BracketedExpression)
37+
{}
3738

38-
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
39+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
3940
{
40-
return Declarations.Where(item => item.DeclarationType == DeclarationType.BracketedExpression)
41-
.Select(item => new DeclarationInspectionResult(this, string.Format(InspectionResults.HostSpecificExpressionInspection, item.IdentifierName), item));
41+
return true;
42+
}
43+
44+
protected override string ResultDescription(Declaration declaration)
45+
{
46+
return string.Format(InspectionResults.HostSpecificExpressionInspection, declaration.IdentifierName);
4247
}
4348
}
4449
}

0 commit comments

Comments
 (0)