Skip to content

Commit 23625ac

Browse files
committed
extend ByRefAssignment check to VariableNotAssigned inspection
1 parent 5c40f06 commit 23625ac

File tree

3 files changed

+41
-2
lines changed

3 files changed

+41
-2
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotAssignedInspection.cs

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,8 @@
22
using System.Linq;
33
using Rubberduck.Inspections.Abstract;
44
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing;
6+
using Rubberduck.Parsing.Grammar;
57
using Rubberduck.Parsing.Inspections.Abstract;
68
using Rubberduck.Resources.Inspections;
79
using Rubberduck.Parsing.Symbols;
@@ -25,11 +27,21 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2527
!declaration.IsWithEvents
2628
&& State.DeclarationFinder.MatchName(declaration.AsTypeName).All(item => item.DeclarationType != DeclarationType.UserDefinedType) // UDT variables don't need to be assigned
2729
&& !declaration.IsSelfAssigned
28-
&& !declaration.References.Any(reference => reference.IsAssignment))
30+
&& !declaration.References.Any(reference => reference.IsAssignment || IsAssignedByRefArgument(reference.ParentScoping, reference)))
2931
.Where(result => !IsIgnoringInspectionResultFor(result, AnnotationName));
3032

3133
return declarations.Select(issue =>
3234
new DeclarationInspectionResult(this, string.Format(InspectionResults.VariableNotAssignedInspection, issue.IdentifierName), issue));
3335
}
36+
37+
private bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierReference reference)
38+
{
39+
var argExpression = reference.Context.GetAncestor<VBAParser.ArgumentExpressionContext>();
40+
var parameter = State.DeclarationFinder.FindParameterFromArgument(argExpression, enclosingProcedure);
41+
42+
// note: not recursive, by design.
43+
return (parameter.IsImplicitByRef || parameter.IsByRef)
44+
&& parameter.References.Any(r => r.IsAssignment);
45+
}
3446
}
3547
}

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -533,7 +533,9 @@ public IEnumerable<Declaration> MatchName(string name)
533533

534534
public ParameterDeclaration FindParameterFromArgument(VBAParser.ArgumentExpressionContext argExpression, Declaration enclosingProcedure)
535535
{
536-
if (argExpression?.GetDescendent<VBAParser.ParenthesizedExprContext>() != null || argExpression?.BYVAL() != null)
536+
if (argExpression == null ||
537+
argExpression.GetDescendent<VBAParser.ParenthesizedExprContext>() != null ||
538+
argExpression.BYVAL() != null)
537539
{
538540
// not an argument, or argument is parenthesized and thus passed ByVal
539541
return null;

RubberduckTests/Inspections/VariableNotAssignedInspectionTests.cs

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -94,6 +94,31 @@ Dim var2 as String
9494
}
9595
}
9696

97+
[Test]
98+
[Category("Inspections")]
99+
public void VariableNotAssigned_GivenByRefAssignment_DoesNotReturnResult()
100+
{
101+
const string inputCode = @"
102+
Sub Foo()
103+
Dim var1 As String
104+
Bar var1
105+
End Sub
106+
107+
Sub Bar(ByRef value As String)
108+
value = ""test""
109+
End Sub
110+
";
111+
112+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
113+
using (var state = MockParser.CreateAndParse(vbe.Object))
114+
{
115+
116+
var inspection = new VariableNotAssignedInspection(state);
117+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
118+
119+
Assert.IsFalse(inspectionResults.Any());
120+
}
121+
}
97122
[Test]
98123
[Category("Inspections")]
99124
public void VariableNotAssigned_Ignored_DoesNotReturnResult()

0 commit comments

Comments
 (0)