Skip to content

Commit 0d880c1

Browse files
committed
fixes #3765
1 parent bbb9d72 commit 0d880c1

File tree

3 files changed

+101
-114
lines changed

3 files changed

+101
-114
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
using Rubberduck.Inspections.Abstract;
66
using Rubberduck.Inspections.Results;
77
using Rubberduck.Parsing;
8+
using Rubberduck.Parsing.Grammar;
89
using Rubberduck.Parsing.Inspections.Abstract;
910
using Rubberduck.Resources.Inspections;
1011
using Rubberduck.Parsing.Symbols;
@@ -30,7 +31,7 @@ public UnassignedVariableUsageInspection(RubberduckParserState state)
3031
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3132
{
3233
var declarations = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
33-
.Where(declaration =>
34+
.Where(declaration => !declaration.IsArray &&
3435
State.DeclarationFinder.MatchName(declaration.AsTypeName)
3536
.All(d => d.DeclarationType != DeclarationType.UserDefinedType)
3637
&& !declaration.IsSelfAssigned
@@ -43,12 +44,22 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4344
.SelectMany(d => d.References)
4445
.Distinct()
4546
.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
47+
.Where(r => !r.Context.TryGetAncestor<VBAParser.RedimStmtContext>(out _) && !IsArraySubscriptAssignment(r))
4648
.Select(r => new IdentifierReferenceInspectionResult(this,
4749
string.Format(InspectionResults.UnassignedVariableUsageInspection, r.IdentifierName),
4850
State,
4951
r)).ToList();
5052
}
5153

54+
private static bool IsArraySubscriptAssignment(IdentifierReference reference)
55+
{
56+
var isLetAssignment = reference.Context.TryGetAncestor<VBAParser.LetStmtContext>(out var letStmt);
57+
var isSetAssignment = reference.Context.TryGetAncestor<VBAParser.SetStmtContext>(out var setStmt);
58+
59+
return isLetAssignment && letStmt.lExpression() is VBAParser.IndexExprContext ||
60+
isSetAssignment && setStmt.lExpression() is VBAParser.IndexExprContext;
61+
}
62+
5263
private static bool DeclarationReferencesContainsReference(Declaration parentDeclaration, Declaration target)
5364
{
5465
foreach (var targetReference in target.References)

RubberduckTests/Inspections/AssignmentNotUsedInspectionTests.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,7 @@ public void IgnoresImplicitArrays()
4545
const string code = @"
4646
Sub Foo()
4747
Dim bar As Variant
48+
ReDim bar(1 To 10)
4849
bar(1) = ""Z""
4950
End Sub
5051
";

RubberduckTests/Inspections/UnassignedVariableUsageInspectionTests.cs

Lines changed: 88 additions & 113 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,9 @@
1+
using System.Collections.Generic;
12
using System.Linq;
23
using System.Threading;
34
using NUnit.Framework;
45
using Rubberduck.Inspections.Concrete;
6+
using Rubberduck.Parsing.Inspections.Abstract;
57
using Rubberduck.VBEditor.SafeComWrappers;
68
using RubberduckTests.Mocks;
79

@@ -10,194 +12,167 @@ namespace RubberduckTests.Inspections
1012
[TestFixture]
1113
public class UnassignedVariableUsageInspectionTests
1214
{
13-
[Test]
14-
[Category("Inspections")]
15-
public void UnassignedVariableUsage_ReturnsResult()
15+
private IEnumerable<IInspectionResult> GetInspectionResults(string code)
1616
{
17-
const string inputCode = @"
18-
Sub Foo()
19-
Dim b As Boolean
20-
Dim bb As Boolean
21-
bb = b
22-
End Sub";
23-
24-
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
17+
var vbe = MockVbeBuilder.BuildFromSingleModule(code, ComponentType.ClassModule, out _);
2518
using (var state = MockParser.CreateAndParse(vbe.Object))
2619
{
2720

2821
var inspection = new UnassignedVariableUsageInspection(state);
29-
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
30-
31-
Assert.AreEqual(1, inspectionResults.Count());
22+
return inspection.GetInspectionResults(CancellationToken.None);
3223
}
3324
}
3425

35-
// this test will eventually be removed once we can fire the inspection on a specific reference
3626
[Test]
3727
[Category("Inspections")]
38-
public void UnassignedVariableUsage_ReturnsSingleResult_MultipleReferences()
28+
public void IgnoresExplicitArrays()
3929
{
40-
const string inputCode =
41-
@"Sub tester()
42-
Dim myarr() As Variant
43-
Dim i As Long
44-
45-
ReDim myarr(1 To 10)
46-
47-
For i = 1 To 10
48-
DoSomething myarr(i)
49-
Next
50-
30+
const string code = @"
31+
Sub Foo()
32+
Dim bar() As String
33+
bar(1) = ""value""
5134
End Sub
35+
";
36+
var results = GetInspectionResults(code);
37+
Assert.AreEqual(0, results.Count());
38+
}
5239

53-
Sub DoSomething(ByVal foo As Variant)
40+
[Test]
41+
[Category("Inspections")]
42+
public void IgnoresArrayReDim()
43+
{
44+
const string code = @"
45+
Sub Foo()
46+
Dim bar As Variant
47+
ReDim bar(1 To 10)
5448
End Sub
5549
";
50+
var results = GetInspectionResults(code);
51+
Assert.AreEqual(0, results.Count());
52+
}
5653

57-
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
58-
using (var state = MockParser.CreateAndParse(vbe.Object))
59-
{
60-
61-
var inspection = new UnassignedVariableUsageInspection(state);
62-
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
54+
[Test]
55+
[Category("Inspections")]
56+
public void IgnoresArraySubscripts()
57+
{
58+
const string code = @"
59+
Sub Foo()
60+
Dim bar As Variant
61+
ReDim bar(1 To 10)
62+
bar(1) = 42
63+
End Sub
64+
";
65+
var results = GetInspectionResults(code);
66+
Assert.AreEqual(0, results.Count());
67+
}
6368

64-
Assert.AreEqual(2, inspectionResults.Count());
65-
}
69+
[Test]
70+
[Category("Inspections")]
71+
public void UnassignedVariableUsage_ReturnsResult()
72+
{
73+
const string code = @"
74+
Sub Foo()
75+
Dim b As Boolean
76+
Dim bb As Boolean
77+
bb = b
78+
End Sub
79+
";
80+
var results = GetInspectionResults(code);
81+
Assert.AreEqual(1, results.Count());
6682
}
6783

6884
[Test]
6985
[Category("Inspections")]
7086
public void UnassignedVariableUsage_DoesNotReturnResult()
7187
{
72-
const string inputCode =
73-
@"Sub Foo()
88+
const string code = @"
89+
Sub Foo()
7490
Dim b As Boolean
7591
Dim bb As Boolean
7692
b = True
7793
bb = b
78-
End Sub";
79-
80-
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
81-
using (var state = MockParser.CreateAndParse(vbe.Object))
82-
{
83-
84-
var inspection = new UnassignedVariableUsageInspection(state);
85-
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
94+
End Sub
95+
";
8696

87-
Assert.IsFalse(inspectionResults.Any());
88-
}
97+
var results = GetInspectionResults(code);
98+
Assert.AreEqual(0, results.Count());
8999
}
90100

91101
[Test]
92102
[Category("Inspections")]
93103
public void UnassignedVariableUsage_Ignored_DoesNotReturnResult()
94104
{
95-
const string inputCode =
96-
@"Sub Foo()
105+
const string code = @"
106+
Sub Foo()
97107
Dim b As Boolean
98108
Dim bb As Boolean
99109
100110
'@Ignore UnassignedVariableUsage
101111
bb = b
102-
End Sub";
103-
104-
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
105-
using (var state = MockParser.CreateAndParse(vbe.Object))
106-
{
107-
108-
var inspection = new UnassignedVariableUsageInspection(state);
109-
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
110-
111-
Assert.IsFalse(inspectionResults.Any());
112-
}
112+
End Sub
113+
";
114+
var results = GetInspectionResults(code);
115+
Assert.AreEqual(0, results.Count());
113116
}
114117

115118
[Test]
116119
[Category("Inspections")]
117120
public void UnassignedVariableUsage_Ignored_DoesNotReturnResultMultipleIgnores()
118121
{
119-
const string inputCode =
120-
@"Sub Foo()
122+
const string code = @"
123+
Sub Foo()
121124
Dim b As Boolean
122125
Dim bb As Boolean
123126
124127
'@Ignore UnassignedVariableUsage, VariableNotAssigned
125128
bb = b
126-
End Sub";
127-
128-
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
129-
using (var state = MockParser.CreateAndParse(vbe.Object))
130-
{
131-
132-
var inspection = new UnassignedVariableUsageInspection(state);
133-
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
134-
135-
Assert.IsFalse(inspectionResults.Any());
136-
}
129+
End Sub
130+
";
131+
var results = GetInspectionResults(code);
132+
Assert.AreEqual(0, results.Count());
137133
}
138134

139135
[Test]
140136
[Category("Inspections")]
141137
public void UnassignedVariableUsage_NoResultIfNoReferences()
142138
{
143-
const string inputCode =
144-
@"Sub DoSomething()
139+
const string code = @"
140+
Sub DoSomething()
145141
Dim foo
146-
End Sub";
147-
148-
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
149-
using (var state = MockParser.CreateAndParse(vbe.Object))
150-
{
151-
152-
var inspection = new UnassignedVariableUsageInspection(state);
153-
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
154-
155-
Assert.IsFalse(inspectionResults.Any());
156-
}
142+
End Sub
143+
";
144+
var results = GetInspectionResults(code);
145+
Assert.AreEqual(0, results.Count());
157146
}
158147

159148
[Test]
160149
[Ignore("Test concurrency issue. Only passes if run individually.")]
161150
[Category("Inspections")]
162151
public void UnassignedVariableUsage_NoResultForLenFunction()
163152
{
164-
const string inputCode =
165-
@"Sub DoSomething()
153+
const string code = @"
154+
Sub DoSomething()
166155
Dim foo As LongPtr
167156
Debug.Print Len(foo)
168-
End Sub";
169-
170-
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
171-
using (var state = MockParser.CreateAndParse(vbe.Object))
172-
{
173-
174-
var inspection = new UnassignedVariableUsageInspection(state);
175-
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
176-
177-
Assert.IsFalse(inspectionResults.Any());
178-
}
157+
End Sub
158+
";
159+
var results = GetInspectionResults(code);
160+
Assert.AreEqual(0, results.Count());
179161
}
180162

181163
[Test]
182164
[Ignore("Test concurrency issue. Only passes if run individually.")]
183165
[Category("Inspections")]
184166
public void UnassignedVariableUsage_NoResultForLenBFunction()
185167
{
186-
const string inputCode =
187-
@"Sub DoSomething()
168+
const string code = @"
169+
Sub DoSomething()
188170
Dim foo As LongPtr
189171
Debug.Print LenB(foo)
190-
End Sub";
191-
192-
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
193-
using (var state = MockParser.CreateAndParse(vbe.Object))
194-
{
195-
196-
var inspection = new UnassignedVariableUsageInspection(state);
197-
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
198-
199-
Assert.IsFalse(inspectionResults.Any());
200-
}
172+
End Sub
173+
";
174+
var results = GetInspectionResults(code);
175+
Assert.AreEqual(0, results.Count());
201176
}
202177

203178
[Test]

0 commit comments

Comments
 (0)