Skip to content

Commit e9f88e0

Browse files
authored
Merge pull request #4604 from MDoerner/FixForVariableNotSetInspection
Fix for variable not set inspection
2 parents 406bbb0 + e6bc9e1 commit e9f88e0

File tree

4 files changed

+185
-70
lines changed

4 files changed

+185
-70
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableRequiresSetAssignmentEvaluator.cs

Lines changed: 58 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using Rubberduck.Parsing.VBA;
55
using System.Diagnostics;
66
using System.Linq;
7+
using Rubberduck.VBEditor;
78

89
namespace Rubberduck.Inspections
910
{
@@ -52,13 +53,7 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
5253
{
5354
// get the members of the returning type, a default member could make us lie otherwise
5455
var classModule = declaration.AsTypeDeclaration as ClassModuleDeclaration;
55-
if (classModule?.DefaultMember == null)
56-
{
57-
return true;
58-
}
59-
var parameters = (classModule.DefaultMember as IParameterizedDeclaration)?.Parameters;
60-
// assign declaration is an object without a default parameterless (or with all parameters optional) member - LHS needs a 'Set' keyword.
61-
return parameters != null && parameters.All(p => p.IsOptional);
56+
return !HasPotentiallyNonObjectParameterlessDefaultMember(classModule);
6257
}
6358

6459
// assigned declaration is a variant. we need to know about the RHS of the assignment.
@@ -75,9 +70,30 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
7570
return false;
7671
}
7772

78-
if (expression is VBAParser.NewExprContext)
73+
74+
var module = Declaration.GetModuleParent(reference.ParentScoping);
75+
76+
if (expression is VBAParser.NewExprContext newExpr)
7977
{
80-
// RHS expression is newing up an object reference - LHS needs a 'Set' keyword:
78+
var newTypeExpression = newExpr.expression();
79+
80+
// todo resolve expression type
81+
82+
//Covers the case of a single type on the RHS of the assignment.
83+
var simpleTypeName = newTypeExpression.GetDescendent<VBAParser.SimpleNameExprContext>();
84+
if (simpleTypeName != null && simpleTypeName.GetText() == newTypeExpression.GetText())
85+
{
86+
var qualifiedIdentifierSelection = new QualifiedSelection(module.QualifiedModuleName,
87+
simpleTypeName.identifier().GetSelection());
88+
var identifierText = simpleTypeName.identifier().GetText();
89+
return declarationFinderProvider.DeclarationFinder.IdentifierReferences(qualifiedIdentifierSelection)
90+
.Select(identifierReference => identifierReference.Declaration)
91+
.Where(decl => identifierText == decl.IdentifierName)
92+
.OfType<ClassModuleDeclaration>()
93+
.Any(typeDecl => !HasPotentiallyNonObjectParameterlessDefaultMember(typeDecl));
94+
}
95+
//Here, we err on the side of false-positives, but that seems more appropriate than not to treat qualified type expressions incorrectly.
96+
//Whether there is a legitimate use here for default members is questionable anyway.
8197
return true;
8298
}
8399

@@ -93,20 +109,48 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
93109
}
94110

95111
// todo resolve expression return type
96-
var project = Declaration.GetProjectParent(reference.ParentScoping);
97-
var module = Declaration.GetModuleParent(reference.ParentScoping);
98112

113+
//Covers the case of a single variable on the RHS of the assignment.
99114
var simpleName = expression.GetDescendent<VBAParser.SimpleNameExprContext>();
100-
if (simpleName != null)
115+
if (simpleName != null && simpleName.GetText() == expression.GetText())
101116
{
102-
return declarationFinderProvider.DeclarationFinder.MatchName(simpleName.identifier().GetText())
103-
.Any(d => AccessibilityCheck.IsAccessible(project, module, reference.ParentScoping, d) && d.IsObject);
117+
var qualifiedIdentifierSelection = new QualifiedSelection(module.QualifiedModuleName,
118+
simpleName.identifier().GetSelection());
119+
return declarationFinderProvider.DeclarationFinder.IdentifierReferences(qualifiedIdentifierSelection)
120+
.Select(identifierReference => identifierReference.Declaration)
121+
.Where(decl => decl.IsObject
122+
&& simpleName.identifier().GetText() == decl.IdentifierName)
123+
.Select(typeDeclaration => typeDeclaration.AsTypeDeclaration as ClassModuleDeclaration)
124+
.Any(typeDecl => !HasPotentiallyNonObjectParameterlessDefaultMember(typeDecl));
104125
}
105126

127+
var project = Declaration.GetProjectParent(reference.ParentScoping);
128+
129+
//todo: Use code path analysis to ensure that we are really picking up the last assignment to the RHS.
106130
// is the reference referring to something else in scope that's a object?
107131
return declarationFinderProvider.DeclarationFinder.MatchName(expression.GetText())
108132
.Any(decl => (decl.DeclarationType.HasFlag(DeclarationType.ClassModule) || Tokens.Object.Equals(decl.AsTypeName))
109133
&& AccessibilityCheck.IsAccessible(project, module, reference.ParentScoping, decl));
110134
}
135+
136+
private static bool HasPotentiallyNonObjectParameterlessDefaultMember(ClassModuleDeclaration classModule)
137+
{
138+
var defaultMember = classModule?.DefaultMember;
139+
140+
if (defaultMember == null)
141+
{
142+
return false;
143+
}
144+
145+
var parameters = (defaultMember as IParameterizedDeclaration)?.Parameters;
146+
// assign declaration is an object without a default parameterless (or with all parameters optional) member - LHS needs a 'Set' keyword.
147+
if (parameters != null && parameters.Any(p => !p.IsOptional))
148+
{
149+
return false;
150+
}
151+
152+
var defaultMemberType = defaultMember.AsTypeDeclaration as ClassModuleDeclaration;
153+
return defaultMemberType == null || HasPotentiallyNonObjectParameterlessDefaultMember(defaultMemberType);
154+
}
111155
}
112156
}

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1177,6 +1177,16 @@ public IEnumerable<IdentifierReference> IdentifierReferences(QualifiedModuleName
11771177
: Enumerable.Empty<IdentifierReference>();
11781178
}
11791179

1180+
/// <summary>
1181+
/// Gets all identifier references with the specified selection.
1182+
/// </summary>
1183+
public IEnumerable<IdentifierReference> IdentifierReferences(QualifiedSelection selection)
1184+
{
1185+
return _referencesBySelection.TryGetValue(selection, out var value)
1186+
? value
1187+
: Enumerable.Empty<IdentifierReference>();
1188+
}
1189+
11801190
/// <summary>
11811191
/// Gets all identifier references in the specified member.
11821192
/// </summary>

RubberduckTests/Inspections/ObjectVariableNotSetInspectionTests.cs

Lines changed: 113 additions & 44 deletions
Original file line numberDiff line numberDiff line change
@@ -155,32 +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_GivenVariantVariableAssignedRange_ReturnsResult()
161-
{
162-
var expectResultCount = 1;
163-
var input =
164-
@"
165-
Private Sub TestSub(ByRef testParam As Variant)
166-
testParam = Range(""A1:C1"")
167-
End Sub";
168-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel.1.8.xml");
169-
}
170-
171-
[Test]
172-
[Category("Inspections")]
173-
public void ObjectVariableNotSet_GivenVariantVariableAssignedDeclaredRange_ReturnsResult()
174-
{
175-
var expectResultCount = 1;
176-
var input =
177-
@"
178-
Private Sub TestSub(ByRef testParam As Variant, target As Range)
179-
testParam = target
180-
End Sub";
181-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel.1.8.xml");
182-
}
183-
184158
[Test]
185159
[Category("Inspections")]
186160
public void ObjectVariableNotSet_GivenVariantVariableAssignedBaseType_ReturnsNoResult()
@@ -195,24 +169,6 @@ Dim target As Variant
195169
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount);
196170
}
197171

198-
[Test]
199-
[Category("Inspections")]
200-
public void ObjectVariableNotSet_GivenObjectVariableNotSet_ReturnsResult()
201-
{
202-
var expectResultCount = 1;
203-
var input =
204-
@"
205-
Private Sub Workbook_Open()
206-
207-
Dim target As Range
208-
target = Range(""A1"")
209-
210-
target.Value = ""forgot something?""
211-
212-
End Sub";
213-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel.1.8.xml");
214-
}
215-
216172
[Test]
217173
[Category("Inspections")]
218174
public void ObjectVariableNotSet_GivenObjectVariableNotSet_Ignored_DoesNotReturnResult()
@@ -483,6 +439,119 @@ Dim bar As Variant
483439
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount);
484440
}
485441

442+
[Test]
443+
[Category("Inspections")]
444+
public void ObjectVariableNotSet_ComplexExpressionOnRHSWithMemberAccess_ReturnsNoResult()
445+
{
446+
447+
var expectResultCount = 0;
448+
var input =
449+
@"
450+
Private Sub Test()
451+
Dim foo As Variant
452+
Dim bar As Collection
453+
Set bar = New Collection
454+
bar.Add ""x"", ""x""
455+
foo = ""Test"" & bar.Item(""x"")
456+
End Sub";
457+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "VBA.4.2");
458+
}
459+
460+
[Test]
461+
[Category("Inspections")]
462+
public void ObjectVariableNotSet_SingleRHSVariableCaseRespectsDeclarationShadowing()
463+
{
464+
465+
var expectResultCount = 0;
466+
var input =
467+
@"
468+
Private bar As Collection
469+
470+
Private Sub Test()
471+
Dim foo As Variant
472+
Dim bar As Long
473+
bar = 42
474+
foo = bar
475+
End Sub";
476+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount);
477+
}
478+
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+
486555
[Test]
487556
[Category("Inspections")]
488557
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)