Skip to content

Commit 7f73cf3

Browse files
committed
extended ByRefAssignment logic to UnassignedVariableUsage inspection
1 parent b25458a commit 7f73cf3

File tree

2 files changed

+33
-3
lines changed

2 files changed

+33
-3
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4141

4242
return declarations
4343
.Where(d => d.References.Any() && !excludedDeclarations.Any(excl => DeclarationReferencesContainsReference(excl, d)))
44-
.SelectMany(d => d.References)
44+
.SelectMany(d => d.References.Where(r => !IsAssignedByRefArgument(r.ParentScoping, r)))
4545
.Distinct()
4646
.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
4747
.Where(r => !r.Context.TryGetAncestor<VBAParser.RedimStmtContext>(out _) && !IsArraySubscriptAssignment(r))
@@ -51,6 +51,17 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5151
r)).ToList();
5252
}
5353

54+
private bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierReference reference)
55+
{
56+
var argExpression = reference.Context.GetAncestor<VBAParser.ArgumentExpressionContext>();
57+
var parameter = State.DeclarationFinder.FindParameterFromArgument(argExpression, enclosingProcedure);
58+
59+
// note: not recursive, by design.
60+
return parameter != null
61+
&& (parameter.IsImplicitByRef || parameter.IsByRef)
62+
&& parameter.References.Any(r => r.IsAssignment);
63+
}
64+
5465
private static bool IsArraySubscriptAssignment(IdentifierReference reference)
5566
{
5667
var isLetAssignment = reference.Context.TryGetAncestor<VBAParser.LetStmtContext>(out var letStmt);

RubberduckTests/Inspections/UnassignedVariableUsageInspectionTests.cs

Lines changed: 21 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -12,9 +12,9 @@ namespace RubberduckTests.Inspections
1212
[TestFixture]
1313
public class UnassignedVariableUsageInspectionTests
1414
{
15-
private IEnumerable<IInspectionResult> GetInspectionResults(string code)
15+
private IEnumerable<IInspectionResult> GetInspectionResults(string code, ComponentType componentType = ComponentType.ClassModule)
1616
{
17-
var vbe = MockVbeBuilder.BuildFromSingleModule(code, ComponentType.ClassModule, out _);
17+
var vbe = MockVbeBuilder.BuildFromSingleModule(code, componentType, out _);
1818
using (var state = MockParser.CreateAndParse(vbe.Object))
1919
{
2020

@@ -132,6 +132,25 @@ End Sub
132132
Assert.AreEqual(0, results.Count());
133133
}
134134

135+
[Test]
136+
[Category("Inspections")]
137+
public void UnassignedVariableUsage_NoResultForAssignedByRefReference()
138+
{
139+
const string code = @"
140+
Sub DoSomething()
141+
Dim foo
142+
AssignThing foo
143+
Debug.Print foo
144+
End Sub
145+
146+
Sub AssignThing(ByRef thing As Variant)
147+
thing = 42
148+
End Sub
149+
";
150+
var results = GetInspectionResults(code, ComponentType.StandardModule);
151+
Assert.AreEqual(0, results.Count());
152+
}
153+
135154
[Test]
136155
[Category("Inspections")]
137156
public void UnassignedVariableUsage_NoResultIfNoReferences()

0 commit comments

Comments
 (0)