Skip to content

Commit

Permalink
Merge pull request #5495 from BZngr/5490_FalsePositive
Browse files Browse the repository at this point in the history
ProcedureNotUsedInspection false positive for PropertyLet
  • Loading branch information
retailcoder committed Jun 7, 2020
2 parents cfe1ad3 + 1b088d5 commit 69bfff3
Show file tree
Hide file tree
Showing 2 changed files with 121 additions and 10 deletions.
@@ -1,3 +1,4 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
Expand All @@ -14,32 +15,92 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
/// </summary>
/// <why>
/// Unused procedures are dead code that should probably be removed. Note, a procedure may be effectively "not used" in code, but attached to some
/// Shape object in the host document: in such cases the inspection result should be ignored. An event handler procedure that isn't being
/// resolved as such, may also wrongly trigger this inspection.
/// Shape object in the host document: in such cases the inspection result should be ignored.
/// </why>
/// <remarks>
/// Not all unused procedures can/should be removed: ignore any inspection results for
/// event handler procedures and interface members that Rubberduck isn't recognizing as such.
/// Public procedures of Standard Modules are not flagged by this inspection regardless of
/// the presence or absence of user code references.
/// </remarks>
/// <example hasResult="true">
/// <module name="MyModule" type="Standard Module">
/// <module name="Module1" type="Standard Module">
/// <![CDATA[
/// Option Explicit
///
/// Public Sub DoSomething()
/// ' macro is attached to a worksheet Shape.
/// Private Sub DoSomething()
/// End Sub
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="MyModule" type="Standard Module">
/// <module name="Module1" type="Standard Module">
/// <![CDATA[
/// Option Explicit
///
///
/// '@Ignore ProcedureNotUsed
/// Private Sub DoSomething()
/// End Sub
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="Macros" type="Standard Module">
/// <![CDATA[
/// Option Explicit
///
/// Public Sub DoSomething()
/// 'a public procedure in a standard module may be a macro
/// 'attached to a worksheet Shape or invoked by means other than user code.
/// End Sub
/// ]]>
/// </module>
/// </example>
/// <example hasResult="true">
/// <module name="Class1" type="Class Module">
/// <![CDATA[
/// Option Explicit
///
/// Public Sub DoSomething()
/// End Sub
///
/// Public Sub DoSomethingElse()
/// End Sub
/// ]]>
/// </module>
/// <module name="Module1" type="Standard Module">
/// <![CDATA[
/// Option Explicit
///
/// Public Sub ReferenceOneClass1Procedure()
/// Dim target As Class1
/// Set target = new Class1
/// target.DoSomething
/// End Sub
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="Class1" type="Class Module">
/// <![CDATA[
/// Option Explicit
///
/// Public Sub DoSomething()
/// ' macro is attached to a worksheet Shape.
/// End Sub
///
/// Public Sub DoSomethingElse()
/// End Sub
/// ]]>
/// </module>
/// <module name="Module1" type="Standard Module">
/// <![CDATA[
/// Option Explicit
///
/// Public Sub ReferenceAllClass1Procedures()
/// Dim target As Class1
/// Set target = new Class1
/// target.DoSomething
/// target.DoSomethingElse
/// End Sub
/// ]]>
/// </module>
Expand Down Expand Up @@ -78,8 +139,7 @@ public ProcedureNotUsedInspection(IDeclarationFinderProvider declarationFinderPr
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
return !declaration.References
.Any(reference => !reference.IsAssignment
&& !reference.ParentScoping.Equals(declaration)) // recursive calls don't count
.Any(reference => !reference.ParentScoping.Equals(declaration)) // ignore recursive/self-referential calls
&& !finder.FindEventHandlers().Contains(declaration)
&& !IsPublicModuleMember(declaration)
&& !IsClassLifeCycleHandler(declaration)
Expand Down
51 changes: 51 additions & 0 deletions RubberduckTests/Inspections/ProcedureNotUsedInspectionTests.cs
Expand Up @@ -182,6 +182,57 @@ public void ProcedureNotUsed_Ignored_DoesNotReturnResult()
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

//https://github.com/rubberduck-vba/Rubberduck/issues/5490
[TestCase(@"Name = ""Bizz""", 0)]
[TestCase(@"mName = ""Bizz""", 1)]
[Category("Inspections")]
public void PropertyLet(string assignmentCode, int expectedResults)
{
var inputCode =
$@"
Private mName As String
Private Sub Class_Initialize()
{assignmentCode}
End Sub
Private Property Let Name(ByVal value As String)
mName = value
End Property
";

var modules = new(string, string, ComponentType)[]
{
(MockVbeBuilder.TestModuleName, inputCode, ComponentType.ClassModule),
};

Assert.AreEqual(expectedResults, InspectionResultsForModules(modules).Count(result => result.Target.DeclarationType.HasFlag(DeclarationType.Procedure)));
}

[Test]
[Category("Inspections")]
public void RecursiveReferenceOnly_ReturnsResult()
{
var inputCode =
$@"
Private mName As String
Private Property Let Name(ByVal value As String)
mName = value
If Len(mName) > 10 Then
Name = Left(mName, 8)
End If
End Property
";

var modules = new(string, string, ComponentType)[]
{
(MockVbeBuilder.TestModuleName, inputCode, ComponentType.ClassModule),
};

Assert.AreEqual(1, InspectionResultsForModules(modules).Count(result => result.Target.DeclarationType.HasFlag(DeclarationType.Procedure)));
}

[Test]
[Category("Inspections")]
public void InspectionName()
Expand Down

0 comments on commit 69bfff3

Please sign in to comment.