Skip to content

Commit edb6c67

Browse files
committed
Make single variable RHS case in ObjectVariableNotSetInspection respect declaration shadowing
Previously, the inspection simply used `IsAccessible`, which does not care for declaration shadowing. This commit changes this to using the identifier references, for which the resolver has already done all the work.
1 parent 841f851 commit edb6c67

File tree

3 files changed

+36
-2
lines changed

3 files changed

+36
-2
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableRequiresSetAssignmentEvaluator.cs

Lines changed: 7 additions & 2 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
{
@@ -100,10 +101,14 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
100101
var simpleName = expression.GetDescendent<VBAParser.SimpleNameExprContext>();
101102
if (simpleName != null && simpleName.GetText() == expression.GetText())
102103
{
103-
return declarationFinderProvider.DeclarationFinder.MatchName(simpleName.identifier().GetText())
104-
.Any(d => AccessibilityCheck.IsAccessible(project, module, reference.ParentScoping, d) && d.IsObject);
104+
var qualifiedIdentifierSelection = new QualifiedSelection(module.QualifiedModuleName,
105+
simpleName.identifier().GetSelection());
106+
return declarationFinderProvider.DeclarationFinder.IdentifierReferences(qualifiedIdentifierSelection)
107+
.Any(identifierReference => identifierReference.Declaration.IsObject
108+
&& simpleName.identifier().GetText() == identifierReference.Declaration.IdentifierName);
105109
}
106110

111+
//todo: Use code path analysis to ensure that we are really picking up the last assignment to the RHS.
107112
// is the reference referring to something else in scope that's a object?
108113
return declarationFinderProvider.DeclarationFinder.MatchName(expression.GetText())
109114
.Any(decl => (decl.DeclarationType.HasFlag(DeclarationType.ClassModule) || Tokens.Object.Equals(decl.AsTypeName))

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 in the specified module.
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: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -501,6 +501,25 @@ Dim bar As Collection
501501
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, new[]{"VBA.4.2"});
502502
}
503503

504+
[Test]
505+
[Category("Inspections")]
506+
public void ObjectVariableNotSet_SinlgeRHSVariableCaseRespectsDeclarationShadowing()
507+
{
508+
509+
var expectResultCount = 0;
510+
var input =
511+
@"
512+
Private bar As Collection
513+
514+
Private Sub Test()
515+
Dim foo As Variant
516+
Dim bar As Long
517+
bar = 42
518+
foo = bar
519+
End Sub";
520+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, new[] { "VBA.4.2" });
521+
}
522+
504523
[Test]
505524
[Category("Inspections")]
506525
public void ObjectVariableNotSet_LSetOnUDT_ReturnsNoResult()

0 commit comments

Comments
 (0)