Skip to content

Commit 117f00f

Browse files
committed
Treat IUnknown like Object in incompatible Set type inspections
Also adds the missing configurationd for the references libraries in tests.
1 parent 2fc4217 commit 117f00f

File tree

5 files changed

+247
-22
lines changed

5 files changed

+247
-22
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ArgumentWithIncompatibleObjectTypeInspection.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -128,7 +128,9 @@ private bool ArgumentPossiblyLegal(Declaration parameterDeclaration , string ass
128128
|| assignedTypeName == Tokens.Variant
129129
|| assignedTypeName == Tokens.Object
130130
|| HasBaseType(parameterDeclaration, assignedTypeName)
131-
|| HasSubType(parameterDeclaration, assignedTypeName);
131+
|| HasSubType(parameterDeclaration, assignedTypeName)
132+
|| assignedTypeName.EndsWith("stdole.IUnknown")
133+
|| parameterDeclaration.FullAsTypeName.EndsWith("stdole.IUnknown");
132134
}
133135

134136
private static bool HasBaseType(Declaration declaration, string typeName)

Rubberduck.CodeAnalysis/Inspections/Concrete/SetAssignmentWithIncompatibleObjectTypeInspection.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,9 @@ private bool SetAssignmentPossiblyLegal(Declaration declaration, string assigned
135135
|| assignedTypeName == Tokens.Variant
136136
|| assignedTypeName == Tokens.Object
137137
|| HasBaseType(declaration, assignedTypeName)
138-
|| HasSubType(declaration, assignedTypeName);
138+
|| HasSubType(declaration, assignedTypeName)
139+
|| assignedTypeName.EndsWith("stdole.IUnknown")
140+
|| declaration.FullAsTypeName.EndsWith("stdole.IUnknown");
139141
}
140142

141143
private bool HasBaseType(Declaration declaration, string typeName)

RubberduckTests/Inspections/ArgumentWithIncompatibleObjectTypeInspectionTests.cs

Lines changed: 15 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -23,10 +23,12 @@ public class ArgumentWithIncompatibleObjectTypeInspectionTests : InspectionTests
2323
[TestCase("Class1", "TestProject.Class1", 0)]
2424
[TestCase("Interface1", "TestProject.Class1", 0)]
2525
[TestCase("Class1", "TestProject.Interface1", 0)]
26-
[TestCase("Variant", "Whatever", 0)] //Tokens.Variant cannot be used here because it is not a constant expression.
27-
[TestCase("Object", "Whatever", 0)]
28-
[TestCase("Whatever", "Variant", 0)]
29-
[TestCase("Whatever", "Object", 0)]
26+
[TestCase("Variant", "Class1", 0)] //Tokens.Variant cannot be used here because it is not a constant expression.
27+
[TestCase("Object", "Class1", 0)]
28+
[TestCase("IUnknown", "Class1", 0)]
29+
[TestCase("Class1", "Variant", 0)]
30+
[TestCase("Class1", "Object", 0)]
31+
[TestCase("Class1", ":stdole.IUnknown", 0)]
3032
[TestCase("Class1", "TestProject.SomethingIncompatible", 1)]
3133
[TestCase("Class1", "SomethingDifferent", 1)]
3234
[TestCase("TestProject.Class1", "OtherProject.Class1", 1)]
@@ -133,11 +135,18 @@ End Sub
133135

134136
private static IVBE BuildTestVBE(string class1, string interface1, string module1)
135137
{
136-
return new MockVbeBuilder()
138+
var projectBuilder = new MockVbeBuilder()
137139
.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
138140
.AddComponent("Class1", ComponentType.ClassModule, class1)
139141
.AddComponent("Interface1", ComponentType.ClassModule, interface1)
140-
.AddComponent("Module1", ComponentType.StandardModule, module1)
142+
.AddComponent("Module1", ComponentType.StandardModule, module1);
143+
144+
if (module1.Contains("IUnknown"))
145+
{
146+
projectBuilder.AddReference(ReferenceLibrary.StdOle);
147+
}
148+
149+
return projectBuilder
141150
.AddProjectToVbeBuilder()
142151
.Build()
143152
.Object;

RubberduckTests/Inspections/SetAssignmentWithIncompatibleObjectTypeInspectionTests.cs

Lines changed: 218 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -351,6 +351,40 @@ End Sub
351351
Assert.IsFalse(inspectionResults.Any());
352352
}
353353

354+
[Test]
355+
[Category("Inspections")]
356+
public void AssignmentToIUnknown_NoResult()
357+
{
358+
const string class1 =
359+
@"
360+
Private Sub Interface1_DoIt()
361+
End Sub
362+
";
363+
364+
const string consumerModule =
365+
@"
366+
Private Sub TestIt()
367+
Dim cls As IUnknown
368+
Dim otherCls As Class1
369+
370+
Set otherCls = new Class1
371+
Set cls = otherCls
372+
End Sub
373+
";
374+
var testVbe = new MockVbeBuilder()
375+
.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
376+
.AddComponent("Class1", ComponentType.ClassModule, class1)
377+
.AddComponent("Module1", ComponentType.StandardModule, consumerModule)
378+
.AddReference(ReferenceLibrary.StdOle)
379+
.AddProjectToVbeBuilder()
380+
.Build()
381+
.Object;
382+
383+
var inspectionResults = InspectionResults(testVbe);
384+
385+
Assert.IsFalse(inspectionResults.Any());
386+
}
387+
354388
[Test]
355389
[Category("Inspections")]
356390
public void AssignmentOfObject_NoResult()
@@ -409,6 +443,41 @@ End Sub
409443
Assert.IsFalse(inspectionResults.Any());
410444
}
411445

446+
[Test]
447+
[Category("Inspections")]
448+
public void AssignmentOfIUnknown_NoResult()
449+
{
450+
const string class1 =
451+
@"
452+
Private Sub Interface1_DoIt()
453+
End Sub
454+
";
455+
456+
const string consumerModule =
457+
@"
458+
Private Sub TestIt()
459+
Dim cls As Class1
460+
Dim otherCls As IUnknown
461+
462+
Set otherCls = new Class2
463+
Set cls = otherCls
464+
End Sub
465+
";
466+
var testVbe = new MockVbeBuilder()
467+
.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
468+
.AddComponent("Class1", ComponentType.ClassModule, class1)
469+
.AddComponent("Class2", ComponentType.ClassModule, class1)
470+
.AddComponent("Module1", ComponentType.StandardModule, consumerModule)
471+
.AddReference(ReferenceLibrary.StdOle)
472+
.AddProjectToVbeBuilder()
473+
.Build()
474+
.Object;
475+
476+
var inspectionResults = InspectionResults(testVbe);
477+
478+
Assert.IsFalse(inspectionResults.Any());
479+
}
480+
412481
[Test]
413482
[Category("Inspections")]
414483
public void AssignmentOfMeToProperlyTypesVariable_NoResult()
@@ -468,10 +537,10 @@ End Sub
468537
[TestCase("Class1", "TestProject1.Class1", 0)]
469538
[TestCase("Interface1", "TestProject1.Class1", 0)]
470539
[TestCase("Class1", "TestProject1.Interface1", 0)]
471-
[TestCase("Variant", "Whatever", 0)] //Tokens.Variant cannot be used here because it is not a constant expression.
472-
[TestCase("Object", "Whatever", 0)]
473-
[TestCase("Whatever", "Variant", 0)]
474-
[TestCase("Whatever", "Object", 0)]
540+
[TestCase("Variant", "Class1", 0)] //Tokens.Variant cannot be used here because it is not a constant expression.
541+
[TestCase("Object", "Class1", 0)]
542+
[TestCase("Class1", "Variant", 0)]
543+
[TestCase("Class1", "Object", 0)]
475544
[TestCase("Class1", "TestProject1.SomethingIncompatible", 1)]
476545
[TestCase("Class1", "SomethingDifferent", 1)]
477546
[TestCase("TestProject1.Class1", "OtherProject.Class1", 1)]
@@ -521,15 +590,60 @@ End Function
521590
Assert.AreEqual(expectedResultsCount, inspectionResults.Count);
522591
}
523592

593+
[Test]
594+
[Category("Inspections")]
595+
[TestCase("IUnknown", "Class1", 0)]
596+
[TestCase("Class1", ":stdole.IUnknown", 0)]
597+
public void MockedSetTypeEvaluatorTest_Function_IUnknown(string lhsTypeName, string expressionFullTypeName, int expectedResultsCount)
598+
{
599+
const string interface1 =
600+
@"
601+
Private Sub Foo()
602+
End Sub
603+
";
604+
const string class1 =
605+
@"Implements Interface1
606+
607+
Private Sub Interface1_Foo()
608+
End Sub
609+
";
610+
611+
var module1 =
612+
$@"
613+
Private Function Cls() As {lhsTypeName}
614+
Set Cls = expression
615+
End Function
616+
";
617+
618+
var vbe = new MockVbeBuilder()
619+
.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
620+
.AddComponent("Class1", ComponentType.ClassModule, class1)
621+
.AddComponent("Interface1", ComponentType.ClassModule, interface1)
622+
.AddComponent("Module1", ComponentType.StandardModule, module1)
623+
.AddReference(ReferenceLibrary.StdOle)
624+
.AddProjectToVbeBuilder()
625+
.Build()
626+
.Object;
627+
628+
var setTypeResolverMock = new Mock<ISetTypeResolver>();
629+
setTypeResolverMock.Setup(m =>
630+
m.SetTypeName(It.IsAny<VBAParser.ExpressionContext>(), It.IsAny<QualifiedModuleName>()))
631+
.Returns((VBAParser.ExpressionContext context, QualifiedModuleName qmn) => expressionFullTypeName);
632+
633+
var inspectionResults = InspectionResults(vbe, setTypeResolverMock.Object).ToList();
634+
635+
Assert.AreEqual(expectedResultsCount, inspectionResults.Count);
636+
}
637+
524638
[Test]
525639
[Category("Inspections")]
526640
[TestCase("Class1", "TestProject1.Class1", 0)]
527641
[TestCase("Interface1", "TestProject1.Class1", 0)]
528642
[TestCase("Class1", "TestProject1.Interface1", 0)]
529-
[TestCase("Variant", "Whatever", 0)] //Tokens.Variant cannot be used here because it is not a constant expression.
530-
[TestCase("Object", "Whatever", 0)]
531-
[TestCase("Whatever", "Variant", 0)]
532-
[TestCase("Whatever", "Object", 0)]
643+
[TestCase("Variant", "Class1", 0)] //Tokens.Variant cannot be used here because it is not a constant expression.
644+
[TestCase("Object", "Class1", 0)]
645+
[TestCase("Class1", "Variant", 0)]
646+
[TestCase("Class1", "Object", 0)]
533647
[TestCase("Class1", "TestProject1.SomethingIncompatible", 1)]
534648
[TestCase("Class1", "SomethingDifferent", 1)]
535649
[TestCase("TestProject1.Class1", "OtherProject.Class1", 1)]
@@ -580,15 +694,60 @@ End Property
580694
Assert.AreEqual(expectedResultsCount, inspectionResults.Count);
581695
}
582696

697+
[Test]
698+
[Category("Inspections")]
699+
[TestCase("IUnknown", "Class1", 0)]
700+
[TestCase("Class1", ":stdole.IUnknown", 0)]
701+
public void MockedSetTypeEvaluatorTest_PropertyGet_IUnknown(string lhsTypeName, string expressionFullTypeName, int expectedResultsCount)
702+
{
703+
const string interface1 =
704+
@"
705+
Private Sub Foo()
706+
End Sub
707+
";
708+
const string class1 =
709+
@"Implements Interface1
710+
711+
Private Sub Interface1_Foo()
712+
End Sub
713+
";
714+
715+
var module1 =
716+
$@"
717+
Private Property Get Cls() As {lhsTypeName}
718+
Set Cls = expression
719+
End Property
720+
";
721+
722+
var vbe = new MockVbeBuilder()
723+
.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
724+
.AddComponent("Class1", ComponentType.ClassModule, class1)
725+
.AddComponent("Interface1", ComponentType.ClassModule, interface1)
726+
.AddComponent("Module1", ComponentType.StandardModule, module1)
727+
.AddReference(ReferenceLibrary.StdOle)
728+
.AddProjectToVbeBuilder()
729+
.Build()
730+
.Object;
731+
732+
var setTypeResolverMock = new Mock<ISetTypeResolver>();
733+
setTypeResolverMock.Setup(m =>
734+
m.SetTypeName(It.IsAny<VBAParser.ExpressionContext>(), It.IsAny<QualifiedModuleName>()))
735+
.Returns((VBAParser.ExpressionContext context, QualifiedModuleName qmn) => expressionFullTypeName);
736+
737+
var inspectionResults = InspectionResults(vbe, setTypeResolverMock.Object).ToList();
738+
739+
Assert.AreEqual(expectedResultsCount, inspectionResults.Count);
740+
}
741+
583742
[Test]
584743
[Category("Inspections")]
585744
[TestCase("Class1", "TestProject1.Class1", 0)]
586745
[TestCase("Interface1", "TestProject1.Class1", 0)]
587746
[TestCase("Class1", "TestProject1.Interface1", 0)]
588-
[TestCase("Variant", "Whatever", 0)] //Tokens.Variant cannot be used here because it is not a constant expression.
589-
[TestCase("Object", "Whatever", 0)]
590-
[TestCase("Whatever", "Variant", 0)]
591-
[TestCase("Whatever", "Object", 0)]
747+
[TestCase("Variant", "Class1", 0)] //Tokens.Variant cannot be used here because it is not a constant expression.
748+
[TestCase("Object", "Class1", 0)]
749+
[TestCase("Class1", "Variant", 0)]
750+
[TestCase("Class1", "Object", 0)]
592751
[TestCase("Class1", "TestProject1.SomethingIncompatible", 1)]
593752
[TestCase("Class1", "SomethingDifferent", 1)]
594753
[TestCase("TestProject1.Class1", "OtherProject.Class1", 1)]
@@ -641,6 +800,53 @@ End Sub
641800
Assert.AreEqual(expectedResultsCount, inspectionResults.Count);
642801
}
643802

803+
[Test]
804+
[Category("Inspections")]
805+
[TestCase("IUnknown", "Class1", 0)]
806+
[TestCase("Class1", ":stdole.IUnknown", 0)]
807+
public void MockedSetTypeEvaluatorTest_Variable_IUnknown(string lhsTypeName, string expressionFullTypeName, int expectedResultsCount)
808+
{
809+
const string interface1 =
810+
@"
811+
Private Sub Foo()
812+
End Sub
813+
";
814+
const string class1 =
815+
@"Implements Interface1
816+
817+
Private Sub Interface1_Foo()
818+
End Sub
819+
";
820+
821+
var module1 =
822+
$@"
823+
Private Sub TestIt()
824+
Dim cls As {lhsTypeName}
825+
826+
Set cls = expression
827+
End Sub
828+
";
829+
830+
var vbe = new MockVbeBuilder()
831+
.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
832+
.AddComponent("Class1", ComponentType.ClassModule, class1)
833+
.AddComponent("Interface1", ComponentType.ClassModule, interface1)
834+
.AddComponent("Module1", ComponentType.StandardModule, module1)
835+
.AddReference(ReferenceLibrary.StdOle)
836+
.AddProjectToVbeBuilder()
837+
.Build()
838+
.Object;
839+
840+
var setTypeResolverMock = new Mock<ISetTypeResolver>();
841+
setTypeResolverMock.Setup(m =>
842+
m.SetTypeName(It.IsAny<VBAParser.ExpressionContext>(), It.IsAny<QualifiedModuleName>()))
843+
.Returns((VBAParser.ExpressionContext context, QualifiedModuleName qmn) => expressionFullTypeName);
844+
845+
var inspectionResults = InspectionResults(vbe, setTypeResolverMock.Object).ToList();
846+
847+
Assert.AreEqual(expectedResultsCount, inspectionResults.Count);
848+
}
849+
644850
private static IEnumerable<IInspectionResult> InspectionResults(IVBE vbe, ISetTypeResolver setTypeResolver)
645851
{
646852
using (var state = MockParser.CreateAndParse(vbe))

RubberduckTests/Mocks/MockVbeBuilder.cs

Lines changed: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
using System.Linq;
55
using Moq;
66
using Rubberduck.VBEditor;
7-
using Rubberduck.VBEditor.Events;
87
using Rubberduck.VBEditor.SafeComWrappers;
98
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
109

@@ -64,9 +63,16 @@ public class MockVbeBuilder
6463
{
6564
[ReferenceLibrary.VBA] = (ReferenceLibrary.VBA.Name(), ReferenceLibrary.VBA.Path(), 4, 2, true),
6665
[ReferenceLibrary.Excel] = (ReferenceLibrary.Excel.Name(), ReferenceLibrary.Excel.Path(), 1, 8, true),
66+
[ReferenceLibrary.MsOffice] = (ReferenceLibrary.MsOffice.Name(), ReferenceLibrary.MsOffice.Path(), 2, 7, true),
67+
[ReferenceLibrary.StdOle] = (ReferenceLibrary.StdOle.Name(), ReferenceLibrary.StdOle.Path(), 2, 0, true),
68+
[ReferenceLibrary.MsForms] = (ReferenceLibrary.MsForms.Name(), ReferenceLibrary.MsForms.Path(), 2, 0, true),
69+
[ReferenceLibrary.VBIDE] = (ReferenceLibrary.VBIDE.Name(), ReferenceLibrary.VBIDE.Path(), 5, 3, true),
6770
[ReferenceLibrary.Scripting] = (ReferenceLibrary.Scripting.Name(), ReferenceLibrary.Scripting.Path(), 1, 0, true),
71+
[ReferenceLibrary.Regex] = (ReferenceLibrary.Regex.Name(), ReferenceLibrary.Regex.Path(), 5, 5, true),
72+
[ReferenceLibrary.MsXml] = (ReferenceLibrary.MsXml.Name(), ReferenceLibrary.MsXml.Path(), 6, 0, true),
73+
[ReferenceLibrary.ShDoc] = (ReferenceLibrary.ShDoc.Name(), ReferenceLibrary.ShDoc.Path(), 1, 1, true),
6874
[ReferenceLibrary.AdoDb] = (ReferenceLibrary.AdoDb.Name(), ReferenceLibrary.AdoDb.Path(), 6, 1, false),
69-
[ReferenceLibrary.MsForms] = (ReferenceLibrary.MsForms.Name(), ReferenceLibrary.MsForms.Path(), 2, 0, true),
75+
[ReferenceLibrary.AdoRecordset] = (ReferenceLibrary.AdoRecordset.Name(), ReferenceLibrary.AdoRecordset.Path(), 6, 0, false),
7076
};
7177

7278
private readonly Windows _windows = new Windows();

0 commit comments

Comments
 (0)