Skip to content

Commit 3dbdb29

Browse files
authored
Merge pull request #6025 from MDoerner/AlignHandlingOfInterfacesINotUsedInspections
Align handling of interfaces in not used inspections
2 parents 242a112 + 5680516 commit 3dbdb29

8 files changed

+388
-21
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ConstantNotUsedInspection.cs

Lines changed: 18 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,24 @@ public ConstantNotUsedInspection(IDeclarationFinderProvider declarationFinderPro
4545
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
4646
{
4747
return declaration?.Context != null
48-
&& !declaration.References.Any();
48+
&& !declaration.References.Any()
49+
&& !IsPublicInExposedClass(declaration);
50+
}
51+
52+
private static bool IsPublicInExposedClass(Declaration procedure)
53+
{
54+
if (!(procedure.Accessibility == Accessibility.Public
55+
|| procedure.Accessibility == Accessibility.Global))
56+
{
57+
return false;
58+
}
59+
60+
if (!(Declaration.GetModuleParent(procedure) is ClassModuleDeclaration classParent))
61+
{
62+
return false;
63+
}
64+
65+
return classParent.IsExposed;
4966
}
5067

5168
protected override string ResultDescription(Declaration declaration)

Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureNotUsedInspection.cs

Lines changed: 21 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -19,9 +19,9 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
1919
/// Shape object in the host document: in such cases the inspection result should be ignored.
2020
/// </why>
2121
/// <remarks>
22-
/// Not all unused procedures can/should be removed: ignore any inspection results for
23-
/// event handler procedures and interface members that Rubberduck isn't recognizing as such, or annotate them with @EntryPoint.
22+
/// Not all unused procedures can/should be removed: ignore any inspection results for event handler procedures or annotate them with @EntryPoint.
2423
/// Members that are annotated with @EntryPoint (or @ExcelHotkey) are not flagged by this inspection, regardless of the presence or absence of user code references.
24+
/// Moreover, unused public members of exposed class modules will not be reported.
2525
/// </remarks>
2626
/// <example hasResult="true">
2727
/// <module name="Module1" type="Standard Module">
@@ -144,12 +144,28 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
144144
&& !finder.FindEventHandlers().Contains(declaration)
145145
&& !IsClassLifeCycleHandler(declaration)
146146
&& !(declaration is ModuleBodyElementDeclaration member
147-
&& (member.IsInterfaceMember
148-
|| member.IsInterfaceImplementation))
147+
&& member.IsInterfaceImplementation)
149148
&& !declaration.Annotations
150149
.Any(pta => pta.Annotation is ITestAnnotation)
151150
&& !IsDocumentEventHandler(declaration)
152-
&& !IsEntryPoint(declaration);
151+
&& !IsEntryPoint(declaration)
152+
&& !IsPublicInExposedClass(declaration);
153+
}
154+
155+
private static bool IsPublicInExposedClass(Declaration procedure)
156+
{
157+
if(!(procedure.Accessibility == Accessibility.Public
158+
|| procedure.Accessibility == Accessibility.Global))
159+
{
160+
return false;
161+
}
162+
163+
if(!(Declaration.GetModuleParent(procedure) is ClassModuleDeclaration classParent))
164+
{
165+
return false;
166+
}
167+
168+
return classParent.IsExposed;
153169
}
154170

155171
private static bool IsEntryPoint(Declaration procedure) =>

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotAssignedInspection.cs

Lines changed: 18 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,24 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
5353
&& !HasUdtType(declaration, finder) // UDT variables don't need to be assigned
5454
&& !declaration.References.Any(reference => reference.IsAssignment
5555
|| reference.IsReDim //Ignores Variants used as arrays without assignment of an existing one.
56-
|| IsAssignedByRefArgument(reference.ParentScoping, reference, finder));
56+
|| IsAssignedByRefArgument(reference.ParentScoping, reference, finder))
57+
&& !IsPublicInExposedClass(declaration);
58+
}
59+
60+
private static bool IsPublicInExposedClass(Declaration procedure)
61+
{
62+
if (!(procedure.Accessibility == Accessibility.Public
63+
|| procedure.Accessibility == Accessibility.Global))
64+
{
65+
return false;
66+
}
67+
68+
if (!(Declaration.GetModuleParent(procedure) is ClassModuleDeclaration classParent))
69+
{
70+
return false;
71+
}
72+
73+
return classParent.IsExposed;
5774
}
5875

5976
private static bool HasUdtType(Declaration declaration, DeclarationFinder finder)

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotUsedInspection.cs

Lines changed: 20 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -54,9 +54,27 @@ public VariableNotUsedInspection(IDeclarationFinderProvider declarationFinderPro
5454
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
5555
{
5656
// exclude undeclared, see #5439
57-
return !declaration.IsWithEvents && !declaration.IsUndeclared
57+
return !declaration.IsWithEvents
58+
&& !declaration.IsUndeclared
5859
&& declaration.References.All(reference => reference.IsAssignment)
59-
&& !declaration.References.Any(IsForLoopAssignment);
60+
&& !declaration.References.Any(IsForLoopAssignment)
61+
&& !IsPublicInExposedClass(declaration);
62+
}
63+
64+
private static bool IsPublicInExposedClass(Declaration procedure)
65+
{
66+
if (!(procedure.Accessibility == Accessibility.Public
67+
|| procedure.Accessibility == Accessibility.Global))
68+
{
69+
return false;
70+
}
71+
72+
if (!(Declaration.GetModuleParent(procedure) is ClassModuleDeclaration classParent))
73+
{
74+
return false;
75+
}
76+
77+
return classParent.IsExposed;
6078
}
6179

6280
private bool IsForLoopAssignment(IdentifierReference reference)

RubberduckTests/Inspections/ConstantNotUsedInspectionTests.cs

Lines changed: 63 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
using Rubberduck.CodeAnalysis.Inspections;
44
using Rubberduck.CodeAnalysis.Inspections.Concrete;
55
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.VBEditor.SafeComWrappers;
67

78
namespace RubberduckTests.Inspections
89
{
@@ -11,7 +12,7 @@ public class ConstantNotUsedInspectionTests : InspectionTestsBase
1112
{
1213
[Test]
1314
[Category("Inspections")]
14-
public void ConstantNotUsed_ReturnsResult()
15+
public void ConstantNotUsed_ReturnsResult_Local()
1516
{
1617
const string inputCode =
1718
@"Public Sub Foo()
@@ -20,6 +21,45 @@ public void ConstantNotUsed_ReturnsResult()
2021
Assert.AreEqual(1, InspectionResultsForStandardModule(inputCode).Count());
2122
}
2223

24+
[Test]
25+
[Category("Inspections")]
26+
[TestCase("Public")]
27+
[TestCase("Private")]
28+
public void ConstantUsed_ReturnsResult_Module(string scopeIdentifier)
29+
{
30+
var inputCode =
31+
$@"
32+
{scopeIdentifier} Const Bar As Integer = 42
33+
";
34+
Assert.AreEqual(1, InspectionResultsForStandardModule(inputCode).Count());
35+
}
36+
37+
[Test]
38+
[Category("Inspections")]
39+
public void ConstantNotUsed_ReturnsResult_Module_Exposed_Private()
40+
{
41+
var inputCode =
42+
$@"
43+
Attribute VB_Exposed = True
44+
45+
Private Const Bar As Integer = 42
46+
";
47+
Assert.AreEqual(1, InspectionResultsForModules(("Class1", inputCode, ComponentType.ClassModule)).Count());
48+
}
49+
50+
[Test]
51+
[Category("Inspections")]
52+
public void VariableNotUsed_DoesNotReturnResult_Module_Exposed_Public()
53+
{
54+
var inputCode =
55+
$@"
56+
Attribute VB_Exposed = True
57+
58+
Public Const Bar As Integer = 42
59+
";
60+
Assert.AreEqual(0, InspectionResultsForModules(("Class1", inputCode, ComponentType.ClassModule)).Count());
61+
}
62+
2363
[Test]
2464
[Category("Inspections")]
2565
public void ConstantNotUsed_ReturnsResult_MultipleConsts()
@@ -51,14 +91,33 @@ Public Sub Goo(ByVal arg1 As Integer)
5191

5292
[Test]
5393
[Category("Inspections")]
54-
public void ConstantNotUsed_DoesNotReturnResult()
94+
public void ConstantNotUsed_UsedConstant_DoesNotReturnResult_Local()
5595
{
5696
const string inputCode =
5797
@"Public Sub Foo()
5898
Const const1 As Integer = 9
5999
Goo const1
60100
End Sub
61101
102+
Public Sub Goo(ByVal arg1 As Integer)
103+
End Sub";
104+
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
105+
}
106+
107+
[Test]
108+
[Category("Inspections")]
109+
[TestCase("Public")]
110+
[TestCase("Private")]
111+
public void ConstantNotUsed_UsedConstant_DoesNotReturnResult_Module(string scopeIdentifier)
112+
{
113+
var inputCode =
114+
$@"
115+
{scopeIdentifier} Const Bar As Integer = 42
116+
117+
Public Sub Foo()
118+
Goo Bar
119+
End Sub
120+
62121
Public Sub Goo(ByVal arg1 As Integer)
63122
End Sub";
64123
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
@@ -90,6 +149,8 @@ public void ConstantNotUsed_IgnoreModule_All_YieldsNoResult()
90149
const string inputCode =
91150
@"'@IgnoreModule
92151
152+
Public Const Bar As Integer = 42
153+
93154
Public Sub Foo()
94155
Const const1 As Integer = 9
95156
End Sub";

RubberduckTests/Inspections/ProcedureNotUsedInspectionTests.cs

Lines changed: 125 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -15,11 +15,16 @@ public class ProcedureNotUsedInspectionTests : InspectionTestsBase
1515
{
1616
[Test]
1717
[Category("Inspections")]
18-
public void ProcedureNotUsed_ReturnsResult()
18+
[TestCase("Sub", "")]
19+
[TestCase("Function", "")]
20+
[TestCase("Property", " Get")]
21+
[TestCase("Property", " Let")]
22+
[TestCase("Property", " Set")]
23+
public void ProcedureNotUsed_ReturnsResult(string memberType, string memberTypeExtension)
1924
{
20-
const string inputCode =
21-
@"Private Sub Foo()
22-
End Sub";
25+
var inputCode =
26+
$@"Private {memberType}{memberTypeExtension} Foo(arg As Variant)
27+
End {memberType}";
2328

2429
Assert.AreEqual(1, InspectionResultsForStandardModule(inputCode).Count());
2530
}
@@ -82,13 +87,127 @@ public void ProcedureNotUsed_DoesNotReturnResult_InterfaceImplementation()
8287
Private Sub IClass1_DoSomething(ByVal a As Integer)
8388
End Sub";
8489

85-
var modules = new(string, string, ComponentType)[]
90+
var modules = new (string, string, ComponentType)[]
8691
{
8792
("IClass1", inputCode1, ComponentType.ClassModule),
8893
("Class1", inputCode2, ComponentType.ClassModule),
8994
};
9095

91-
Assert.AreEqual(0, InspectionResultsForModules(modules).Count(result => result.Target.DeclarationType == DeclarationType.Procedure));
96+
var relevantResults = InspectionResultsForModules(modules)
97+
.Where(result => result.Target.DeclarationType == DeclarationType.Procedure
98+
&& result.Target.QualifiedModuleName.ComponentName == "Class1");
99+
100+
Assert.AreEqual(0, relevantResults.Count());
101+
}
102+
103+
[Test]
104+
[Category("Inspections")]
105+
public void ProcedureNotUsed_ReturnsResult_ImplementedInterfaceMethod()
106+
{
107+
const string inputCode1 =
108+
@"Public Sub DoSomething(ByVal a As Integer)
109+
End Sub";
110+
const string inputCode2 =
111+
@"Implements IClass1
112+
113+
Private Sub IClass1_DoSomething(ByVal a As Integer)
114+
End Sub";
115+
116+
var modules = new (string, string, ComponentType)[]
117+
{
118+
("IClass1", inputCode1, ComponentType.ClassModule),
119+
("Class1", inputCode2, ComponentType.ClassModule),
120+
};
121+
122+
var results = InspectionResultsForModules(modules);
123+
var relevantResults = results
124+
.Where(result => result.Target.DeclarationType == DeclarationType.Procedure
125+
&& result.Target.QualifiedModuleName.ComponentName == "IClass1");
126+
127+
Assert.AreEqual(1, relevantResults.Count());
128+
}
129+
130+
[Test]
131+
[Category("Inspections")]
132+
public void ProcedureNotUsed_ReturnsResult_MarkedInterfaceMethod()
133+
{
134+
const string inputCode1 =
135+
@"
136+
'@Interface
137+
138+
Public Sub DoSomething(ByVal a As Integer)
139+
End Sub
140+
";
141+
142+
143+
var modules = new (string, string, ComponentType)[]
144+
{
145+
("IClass1", inputCode1, ComponentType.ClassModule)
146+
};
147+
148+
var results = InspectionResultsForModules(modules);
149+
var relevantResults = results
150+
.Where(result => result.Target.DeclarationType == DeclarationType.Procedure
151+
&& result.Target.QualifiedModuleName.ComponentName == "IClass1");
152+
153+
Assert.AreEqual(1, relevantResults.Count());
154+
}
155+
156+
[Test]
157+
[Category("Inspections")]
158+
[TestCase("Sub", "")]
159+
[TestCase("Function", "")]
160+
[TestCase("Property", " Get")]
161+
[TestCase("Property", " Let")]
162+
[TestCase("Property", " Set")]
163+
public void ProcedureNotUsed_DoesNotReturnResult_ExposedClass_Public(string memberType, string memberTypeExtension)
164+
{
165+
var inputCode =
166+
$@"
167+
Attribute VB_Exposed = True
168+
169+
Public {memberType}{memberTypeExtension} Foo(arg As Variant)
170+
End {memberType}";
171+
172+
Assert.AreEqual(0, InspectionResultsForModules(("Class1", inputCode, ComponentType.ClassModule)).Count());
173+
}
174+
175+
[Test]
176+
[Category("Inspections")]
177+
[TestCase("Sub", "")]
178+
[TestCase("Function", "")]
179+
[TestCase("Property", " Get")]
180+
[TestCase("Property", " Let")]
181+
[TestCase("Property", " Set")]
182+
public void ProcedureNotUsed_ReturnsResult_ExposedClass_Private(string memberType, string memberTypeExtension)
183+
{
184+
var inputCode =
185+
$@"
186+
Attribute VB_Exposed = True
187+
188+
Private {memberType}{memberTypeExtension} Foo(arg As Variant)
189+
End {memberType}";
190+
191+
Assert.AreEqual(1, InspectionResultsForModules(("Class1", inputCode, ComponentType.ClassModule)).Count());
192+
}
193+
194+
[Test]
195+
[Category("Inspections")]
196+
[TestCase("Sub", "")]
197+
[TestCase("Function", "")]
198+
[TestCase("Property", " Get")]
199+
[TestCase("Property", " Let")]
200+
[TestCase("Property", " Set")]
201+
public void ProcedureNotUsed_ReturnsResult_ExposedClass_Friend(string memberType, string memberTypeExtension)
202+
{
203+
var inputCode =
204+
$@"
205+
Attribute VB_Exposed = True
206+
207+
Friend {memberType}{memberTypeExtension} Foo(arg As Variant)
208+
End {memberType}";
209+
210+
Assert.AreEqual(1, InspectionResultsForModules(("Class1", inputCode, ComponentType.ClassModule)).Count());
92211
}
93212

94213
[Test]

0 commit comments

Comments
 (0)