Skip to content

Commit

Permalink
Merge pull request #1 from rubberduck-vba/next
Browse files Browse the repository at this point in the history
Riportiamoci a pari
  • Loading branch information
PhilCattivocaratere committed Jul 21, 2022
2 parents a12790c + 19c3104 commit d7a3b8d
Show file tree
Hide file tree
Showing 9 changed files with 298 additions and 7 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,83 @@
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using System.Linq;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Warns about User Defined Type (UDT) members that are never referenced.
/// </summary>
/// <why>
/// Declarations that are never used should be removed.
/// </why>
/// <example hasResult="true">
/// <module name="MyModule" type="Standard Module">
/// <![CDATA[
/// Private Type TTestModule
/// FirstVal As Long
/// End Type
///
/// Private this As TTestModule
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="MyModule" type="Standard Module">
/// <![CDATA[
/// Private Type TTestModule
/// FirstVal As Long
/// End Type
///
/// Private this As TTestModule
///
/// 'UDT Member is assigned but not used
/// Public Sub DoSomething()
/// this.FirstVal = 42
/// End Sub
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="MyModule" type="Standard Module">
/// <![CDATA[
/// Private Type TTestModule
/// FirstVal As Long
/// End Type
///
/// Private this As TTestModule
///
/// 'UDT Member is assigned and read
/// Public Sub DoSomething()
/// this.FirstVal = 42
/// Debug.Print this.FirstVal
/// End Sub
/// ]]>
/// </module>
/// </example>
internal sealed class UDTMemberNotUsedInspection : DeclarationInspectionBase
{
public UDTMemberNotUsedInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.UserDefinedTypeMember)
{}

protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
return declaration.DeclarationType.Equals(DeclarationType.UserDefinedTypeMember)
&& !declaration.References.Any();
}

protected override string ResultDescription(Declaration declaration)
{
var declarationType = declaration.DeclarationType.ToLocalizedString();
var declarationName = declaration.IdentifierName;
return string.Format(
InspectionResults.IdentifierNotUsedInspection,
declarationType,
declarationName);
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,8 @@ public RemoveUnusedDeclarationQuickFix(DeleteDeclarationsRefactoringAction refac
: base(typeof(ConstantNotUsedInspection),
typeof(ProcedureNotUsedInspection),
typeof(VariableNotUsedInspection),
typeof(LineLabelNotUsedInspection))
typeof(LineLabelNotUsedInspection),
typeof(UDTMemberNotUsedInspection))
{
_refactoring = refactoringAction;
}
Expand Down
24 changes: 18 additions & 6 deletions Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

3 changes: 3 additions & 0 deletions Rubberduck.Resources/Inspections/InspectionInfo.resx
Original file line number Diff line number Diff line change
Expand Up @@ -472,4 +472,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu
<data name="PublicEnumerationDeclaredInWorksheetInspection" xml:space="preserve">
<value>Copying a worksheet which contains a public Enum declaration will also create a copy of the Enum declaration. The copied declaration will result in an 'Ambiguous name detected' compiler error. Declaring Enumerations in Standard or Class modules avoids unintentional duplication of an Enum declaration.</value>
</data>
<data name="UDTMemberNotUsedInspection" xml:space="preserve">
<value>A User Defined Type (UDT) member is declared but not used. Consider removing the UDT member declaration.</value>
</data>
</root>
9 changes: 9 additions & 0 deletions Rubberduck.Resources/Inspections/InspectionNames.Designer.cs

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

3 changes: 3 additions & 0 deletions Rubberduck.Resources/Inspections/InspectionNames.resx
Original file line number Diff line number Diff line change
Expand Up @@ -472,4 +472,7 @@
<data name="PublicControlFieldAccessInspection" xml:space="preserve">
<value>Public control field access</value>
</data>
<data name="UDTMemberNotUsedInspection" xml:space="preserve">
<value>User Defined Type member is not used</value>
</data>
</root>

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 1 addition & 0 deletions RubberduckTests/Inspections/GeneralInspectionTests.cs
Original file line number Diff line number Diff line change
Expand Up @@ -84,6 +84,7 @@ public void InspectionResultFormatStringsExist()
{
var inspectionsWithSharedResultFormat = new List<string>
{
typeof(UDTMemberNotUsedInspection).Name,
typeof(ConstantNotUsedInspection).Name,
typeof(ParameterNotUsedInspection).Name,
typeof(ProcedureNotUsedInspection).Name,
Expand Down
170 changes: 170 additions & 0 deletions RubberduckTests/Inspections/UDTMemberNotUsedInspectionTests.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,170 @@
using NUnit.Framework;
using Rubberduck.CodeAnalysis.Inspections;
using Rubberduck.CodeAnalysis.Inspections.Concrete;
using Rubberduck.Parsing.VBA;
using System;
using System.Collections.Generic;
using System.Linq;
using System.Text;
using System.Threading.Tasks;

namespace RubberduckTests.Inspections
{
[TestFixture]
class UDTMemberNotUsedInspectionTests : InspectionTestsBase
{
[Test]
[Category("Inspections")]
[Category(nameof(UDTMemberNotUsedInspection))]
public void ReturnsZeroResult()
{
const string inputCode =
@"
Option Explicit
Private Type TUnitTest
FirstVal As Long
SecondVal As Long
End Type
Private this As TUnitTest
Private Sub TestSub(testVal As Long)
this.FirstVal = testVal * 2
this.SecondVal = testVal
End Sub
";
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

[Test]
[Category("Inspections")]
[Category(nameof(UDTMemberNotUsedInspection))]
public void ReturnsSingleResult()
{
const string inputCode =
@"
Option Explicit
Private Type TUnitTest
FirstVal As Long
SecondVal As Long
End Type
Private this As TUnitTest
Private Sub TestSub(testVal As Long)
this.FirstVal = testVal
End Sub
";
Assert.AreEqual(1, InspectionResultsForStandardModule(inputCode).Count());
}

[Test]
[Category("Inspections")]
[Category(nameof(UDTMemberNotUsedInspection))]
public void ReturnsManyResults()
{
const string inputCode =
@"
Option Explicit
Private Type TUnitTest
FirstVal As Long
SecondVal As Long
ThirdVal As Long
End Type
Private this As TUnitTest
Private Sub TestSub(testVal As Long)
this.SecondVal = testVal
End Sub
";
Assert.AreEqual(2, InspectionResultsForStandardModule(inputCode).Count());
}

[Test]
[Category("Inspections")]
[Category(nameof(UDTMemberNotUsedInspection))]
public void ReturnsResultForNestedUDTMember()
{
const string inputCode =
@"
Option Explicit
Private Type TPair
IDNumber As Long
IDName As String
End Type
Private Type TUnitTest
ID_Name_Pair As TPair
SecondVal As Long
End Type
Private this As TUnitTest
Private Sub TestSub(testVal As Long)
this.ID_Name_Pair.IDNumber = testVal
this.SecondVal = testVal * 2
End Sub
";
Assert.AreEqual(1, InspectionResultsForStandardModule(inputCode).Count());
}

[Test]
[Category("Inspections")]
[Category(nameof(UDTMemberNotUsedInspection))]
public void RespectsIgnoreAnnotation()
{
const string inputCode =
@"
Option Explicit
Private Type TUnitTest
FirstVal As Long
'@Ignore UDTMemberNotUsed
SecondVal As Long
End Type
Private this As TUnitTest
Private Sub TestSub(testVal As Long)
this.FirstVal = testVal
End Sub
";
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

[TestCase("'@IgnoreModule")]
[TestCase("'@IgnoreModule UDTMemberNotUsed")]
[Category("Inspections")]
[Category(nameof(UDTMemberNotUsedInspection))]
public void RespectsIgnoreModuleAnnotation(string annotation)
{
var inputCode =
$@"
{annotation}
Option Explicit
Private Type TUnitTest
FirstVal As Long
SecondVal As Long
End Type
Private this As TUnitTest
Private Sub TestSub(testVal As Long)
this.FirstVal = testVal
End Sub
";
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

protected override IInspection InspectionUnderTest(RubberduckParserState state)
{
return new UDTMemberNotUsedInspection(state);
}
}
}

0 comments on commit d7a3b8d

Please sign in to comment.