Skip to content

Commit 295ecd6

Browse files
committed
Fix evaluation whether a default member has non-optional parameters in ObjectVariableNotSetInspection
Moreover, introduces more tests around default members (partially failing) and removes or alters tests that tested wrong behaviour.
1 parent 332470c commit 295ecd6

File tree

3 files changed

+82
-45
lines changed

3 files changed

+82
-45
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableRequiresSetAssignmentEvaluator.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -59,7 +59,7 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
5959
}
6060
var parameters = (classModule.DefaultMember as IParameterizedDeclaration)?.Parameters;
6161
// assign declaration is an object without a default parameterless (or with all parameters optional) member - LHS needs a 'Set' keyword.
62-
return parameters != null && parameters.All(p => p.IsOptional);
62+
return parameters != null && parameters.Any(p => !p.IsOptional);
6363
}
6464

6565
// assigned declaration is a variant. we need to know about the RHS of the assignment.

RubberduckTests/Inspections/ObjectVariableNotSetInspectionTests.cs

Lines changed: 77 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -155,19 +155,6 @@ Private Sub TestSub(ByRef testParam As Variant)
155155
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "VBA.4.2.xml");
156156
}
157157

158-
[Test]
159-
[Category("Inspections")]
160-
public void ObjectVariableNotSet_GivenVariantVariableAssignedDeclaredRange_ReturnsResult()
161-
{
162-
var expectResultCount = 1;
163-
var input =
164-
@"
165-
Private Sub TestSub(ByRef testParam As Variant, target As Range)
166-
testParam = target
167-
End Sub";
168-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel.1.8.xml");
169-
}
170-
171158
[Test]
172159
[Category("Inspections")]
173160
public void ObjectVariableNotSet_GivenVariantVariableAssignedBaseType_ReturnsNoResult()
@@ -182,24 +169,6 @@ Dim target As Variant
182169
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount);
183170
}
184171

185-
[Test]
186-
[Category("Inspections")]
187-
public void ObjectVariableNotSet_GivenObjectVariableNotSet_ReturnsResult()
188-
{
189-
var expectResultCount = 1;
190-
var input =
191-
@"
192-
Private Sub Workbook_Open()
193-
194-
Dim target As Range
195-
target = Range(""A1"")
196-
197-
target.Value = ""forgot something?""
198-
199-
End Sub";
200-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel.1.8.xml");
201-
}
202-
203172
[Test]
204173
[Category("Inspections")]
205174
public void ObjectVariableNotSet_GivenObjectVariableNotSet_Ignored_DoesNotReturnResult()
@@ -490,7 +459,7 @@ Dim bar As Collection
490459

491460
[Test]
492461
[Category("Inspections")]
493-
public void ObjectVariableNotSet_SinlgeRHSVariableCaseRespectsDeclarationShadowing()
462+
public void ObjectVariableNotSet_SingleRHSVariableCaseRespectsDeclarationShadowing()
494463
{
495464

496465
var expectResultCount = 0;
@@ -507,6 +476,82 @@ Dim bar As Long
507476
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount);
508477
}
509478

479+
[Test]
480+
[Category("Inspections")]
481+
public void ObjectVariableNotSet_SingleRHSVariableCaseRespectsDefaultMembers()
482+
{
483+
var expectResultCount = 0;
484+
var input =
485+
@"
486+
Private Sub Test()
487+
Dim foo As Range
488+
Dim bar As Variant
489+
bar = foo
490+
End Sub";
491+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel.1.8.xml");
492+
}
493+
494+
[Test]
495+
[Category("Inspections")]
496+
public void ObjectVariableNotSet_SingleRHSVariableCaseIdentifiesDefaultMembersNotReturningAnObject()
497+
{
498+
var expectResultCount = 1;
499+
var input =
500+
@"
501+
Private Sub Test()
502+
Dim foo As Recordset
503+
Dim bar As Variant
504+
bar = foo
505+
End Sub";
506+
//The default member of Recordset is Fields, which is an object.
507+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "ADODB.6.1");
508+
}
509+
510+
[Test]
511+
[Category("Inspections")]
512+
public void ObjectVariableNotSet_AssignmentToVarirableWithDefaultMemberReturningAnObject_OneResult()
513+
{
514+
var expectResultCount = 1;
515+
var input =
516+
@"
517+
Private Sub Test()
518+
Dim foo As Recordset
519+
Dim bar As Variant
520+
foo = bar
521+
End Sub";
522+
//The default member of Recordset is Fields, which is an object.
523+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "ADODB.6.1");
524+
}
525+
526+
[Test]
527+
[Category("Inspections")]
528+
public void ObjectVariableNotSet_NewExprWithNonObjectDefaultMember_NoResult()
529+
{
530+
var expectResultCount = 0;
531+
var input =
532+
@"
533+
Private Sub Test()
534+
Dim foo As Variant
535+
foo = New Connection
536+
End Sub";
537+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "ADODB.6.1");
538+
}
539+
540+
[Test]
541+
[Category("Inspections")]
542+
public void ObjectVariableNotSet_NewExprWithObjectOnlyDefaultMember_OneResult()
543+
{
544+
var expectResultCount = 1;
545+
var input =
546+
@"
547+
Private Sub Test()
548+
Dim foo As Variant
549+
foo = New Recordset
550+
End Sub";
551+
//The default member of Recordset is Fields, which is an object.
552+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "ADODB.6.1");
553+
}
554+
510555
[Test]
511556
[Category("Inspections")]
512557
public void ObjectVariableNotSet_LSetOnUDT_ReturnsNoResult()

RubberduckTests/QuickFixes/UseSetKeywordForObjectAssignmentQuickFixTests.cs

Lines changed: 4 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -62,21 +62,13 @@ public void ObjectVariableNotSet_ForFunctionAssignment_ReturnsResult()
6262
{
6363
var inputCode =
6464
@"
65-
Private Function CombineRanges(ByVal source As Range, ByVal toCombine As Range) As Range
66-
If source Is Nothing Then
67-
CombineRanges = toCombine 'no inspection result (but there should be one!)
68-
Else
69-
CombineRanges = Union(source, toCombine) 'no inspection result (but there should be one!)
70-
End If
65+
Private Function ReturnObject(ByVal source As Object) As Object
66+
ReturnObject = source
7167
End Function";
7268
var expectedCode =
7369
@"
74-
Private Function CombineRanges(ByVal source As Range, ByVal toCombine As Range) As Range
75-
If source Is Nothing Then
76-
Set CombineRanges = toCombine 'no inspection result (but there should be one!)
77-
Else
78-
Set CombineRanges = Union(source, toCombine) 'no inspection result (but there should be one!)
79-
End If
70+
Private Function ReturnObject(ByVal source As Object) As Object
71+
Set ReturnObject = source
8072
End Function";
8173

8274
var actualCode = ApplyQuickFixToAllInspectionResults(inputCode, state => new ObjectVariableNotSetInspection(state));

0 commit comments

Comments
 (0)