Skip to content

Commit 0ba0c90

Browse files
committed
Remove restriction to variables on SetAssignmentWithIncompatibleObjectTypeInspection
Also changes the way the set assignments are obtained to increase performance when libraries are referenced.
1 parent 2fe9ab9 commit 0ba0c90

File tree

3 files changed

+131
-16
lines changed

3 files changed

+131
-16
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/SetAssignmentWithIncompatibleObjectTypeInspection.cs

Lines changed: 10 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -95,28 +95,25 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
9595
{
9696
var finder = _declarationFinderProvider.DeclarationFinder;
9797

98-
var offendingAssignments = StronglyTypedObjectVariables(finder)
99-
.SelectMany(SetAssignments)
98+
var setAssignments = finder.AllIdentifierReferences().Where(reference => reference.IsSetAssignment);
99+
100+
var offendingAssignments = setAssignments
101+
.Where(ToBeConsidered)
100102
.Select(setAssignment => SetAssignmentWithAssignedTypeName(setAssignment, finder))
101103
.Where(setAssignmentWithAssignedTypeName => setAssignmentWithAssignedTypeName.assignedTypeName != null
102-
&& !SetAssignmentPossiblyLegal(setAssignmentWithAssignedTypeName));
104+
&& !SetAssignmentPossiblyLegal(setAssignmentWithAssignedTypeName));
103105

104106
return offendingAssignments
105107
.Where(setAssignmentWithAssignedTypeName => !IsIgnored(setAssignmentWithAssignedTypeName.setAssignment))
106108
.Select(setAssignmentWithAssignedTypeName => InspectionResult(setAssignmentWithAssignedTypeName, _declarationFinderProvider));
107109
}
108110

109-
110-
private IEnumerable<Declaration> StronglyTypedObjectVariables(DeclarationFinder declarationFinder)
111-
{
112-
return declarationFinder.DeclarationsWithType(DeclarationType.Variable)
113-
.Where(declaration => declaration.IsObject
114-
&& declaration.AsTypeDeclaration != null);
115-
}
116-
117-
private IEnumerable<IdentifierReference> SetAssignments(Declaration declaration)
111+
private static bool ToBeConsidered(IdentifierReference reference)
118112
{
119-
return declaration.References.Where(reference => reference.IsSetAssignment);
113+
var declaration = reference.Declaration;
114+
return declaration != null
115+
&& declaration.AsTypeDeclaration != null
116+
&& declaration.IsObject;
120117
}
121118

122119
private (IdentifierReference setAssignment, string assignedTypeName) SetAssignmentWithAssignedTypeName(IdentifierReference setAssignment, DeclarationFinder finder)

Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.xml

Lines changed: 2 additions & 2 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

RubberduckTests/Inspections/SetAssignmentWithIncompatibleObjectTypeInspectionTests.cs

Lines changed: 119 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -487,7 +487,125 @@ End Sub
487487
[TestCase("Class1", "OtherProject.Interface1", 1)]
488488
[TestCase("Class1", SetTypeResolver.NotAnObject, 1)] //The RHS is not even an object. (Will show as type NotAnObject in the result.)
489489
[TestCase("Class1", null, 0)] //We could not resolve the Set type, so we do not return a result.
490-
public void MockedSetTypeEvaluatorTest(string lhsTypeName, string expressionFullTypeName, int expectedResultsCount)
490+
public void MockedSetTypeEvaluatorTest_Variable(string lhsTypeName, string expressionFullTypeName, int expectedResultsCount)
491+
{
492+
const string interface1 =
493+
@"
494+
Private Sub Foo()
495+
End Sub
496+
";
497+
const string class1 =
498+
@"Implements Interface1
499+
500+
Private Sub Interface1_Foo()
501+
End Sub
502+
";
503+
504+
var module1 =
505+
$@"
506+
Private Function Cls() As {lhsTypeName}
507+
Set Cls = expression
508+
End Function
509+
";
510+
511+
var vbe = new MockVbeBuilder()
512+
.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
513+
.AddComponent("Class1", ComponentType.ClassModule, class1)
514+
.AddComponent("Interface1", ComponentType.ClassModule, interface1)
515+
.AddComponent("Module1", ComponentType.StandardModule, module1)
516+
.AddProjectToVbeBuilder()
517+
.Build()
518+
.Object;
519+
520+
var setTypeResolverMock = new Mock<ISetTypeResolver>();
521+
setTypeResolverMock.Setup(m =>
522+
m.SetTypeName(It.IsAny<VBAParser.ExpressionContext>(), It.IsAny<QualifiedModuleName>()))
523+
.Returns((VBAParser.ExpressionContext context, QualifiedModuleName qmn) => expressionFullTypeName);
524+
525+
var inspectionResults = InspectionResults(vbe, setTypeResolverMock.Object).ToList();
526+
527+
Assert.AreEqual(expectedResultsCount, inspectionResults.Count);
528+
}
529+
530+
[Test]
531+
[Category("Inspections")]
532+
[TestCase("Class1", "TestProject.Class1", 0)]
533+
[TestCase("Interface1", "TestProject.Class1", 0)]
534+
[TestCase("Class1", "TestProject.Interface1", 0)]
535+
[TestCase("Variant", "Whatever", 0)] //Tokens.Variant cannot be used here because it is not a constant expression.
536+
[TestCase("Object", "Whatever", 0)]
537+
[TestCase("Whatever", "Variant", 0)]
538+
[TestCase("Whatever", "Object", 0)]
539+
[TestCase("Class1", "TestProject.SomethingIncompatible", 1)]
540+
[TestCase("Class1", "SomethingDifferent", 1)]
541+
[TestCase("TestProject.Class1", "OtherProject.Class1", 1)]
542+
[TestCase("TestProject.Interface1", "OtherProject.Class1", 1)]
543+
[TestCase("TestProject.Class1", "OtherProject.Interface1", 1)]
544+
[TestCase("Class1", "OtherProject.Class1", 1)]
545+
[TestCase("Interface1", "OtherProject.Class1", 1)]
546+
[TestCase("Class1", "OtherProject.Interface1", 1)]
547+
[TestCase("Class1", SetTypeResolver.NotAnObject, 1)] //The RHS is not even an object. (Will show as type NotAnObject in the result.)
548+
[TestCase("Class1", null, 0)] //We could not resolve the Set type, so we do not return a result.
549+
public void MockedSetTypeEvaluatorTest_Function(string lhsTypeName, string expressionFullTypeName, int expectedResultsCount)
550+
{
551+
const string interface1 =
552+
@"
553+
Private Sub Foo()
554+
End Sub
555+
";
556+
const string class1 =
557+
@"Implements Interface1
558+
559+
Private Sub Interface1_Foo()
560+
End Sub
561+
";
562+
563+
var module1 =
564+
$@"
565+
Private Property Get Cls() As {lhsTypeName}
566+
Set Cls = expression
567+
End Property
568+
";
569+
570+
var vbe = new MockVbeBuilder()
571+
.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
572+
.AddComponent("Class1", ComponentType.ClassModule, class1)
573+
.AddComponent("Interface1", ComponentType.ClassModule, interface1)
574+
.AddComponent("Module1", ComponentType.StandardModule, module1)
575+
.AddProjectToVbeBuilder()
576+
.Build()
577+
.Object;
578+
579+
var setTypeResolverMock = new Mock<ISetTypeResolver>();
580+
setTypeResolverMock.Setup(m =>
581+
m.SetTypeName(It.IsAny<VBAParser.ExpressionContext>(), It.IsAny<QualifiedModuleName>()))
582+
.Returns((VBAParser.ExpressionContext context, QualifiedModuleName qmn) => expressionFullTypeName);
583+
584+
var inspectionResults = InspectionResults(vbe, setTypeResolverMock.Object).ToList();
585+
586+
Assert.AreEqual(expectedResultsCount, inspectionResults.Count);
587+
}
588+
589+
[Test]
590+
[Category("Inspections")]
591+
[TestCase("Class1", "TestProject.Class1", 0)]
592+
[TestCase("Interface1", "TestProject.Class1", 0)]
593+
[TestCase("Class1", "TestProject.Interface1", 0)]
594+
[TestCase("Variant", "Whatever", 0)] //Tokens.Variant cannot be used here because it is not a constant expression.
595+
[TestCase("Object", "Whatever", 0)]
596+
[TestCase("Whatever", "Variant", 0)]
597+
[TestCase("Whatever", "Object", 0)]
598+
[TestCase("Class1", "TestProject.SomethingIncompatible", 1)]
599+
[TestCase("Class1", "SomethingDifferent", 1)]
600+
[TestCase("TestProject.Class1", "OtherProject.Class1", 1)]
601+
[TestCase("TestProject.Interface1", "OtherProject.Class1", 1)]
602+
[TestCase("TestProject.Class1", "OtherProject.Interface1", 1)]
603+
[TestCase("Class1", "OtherProject.Class1", 1)]
604+
[TestCase("Interface1", "OtherProject.Class1", 1)]
605+
[TestCase("Class1", "OtherProject.Interface1", 1)]
606+
[TestCase("Class1", SetTypeResolver.NotAnObject, 1)] //The RHS is not even an object. (Will show as type NotAnObject in the result.)
607+
[TestCase("Class1", null, 0)] //We could not resolve the Set type, so we do not return a result.
608+
public void MockedSetTypeEvaluatorTest_PropertyGet(string lhsTypeName, string expressionFullTypeName, int expectedResultsCount)
491609
{
492610
const string interface1 =
493611
@"

0 commit comments

Comments
 (0)