Skip to content

Commit bbb9d72

Browse files
committed
fixes #4486
1 parent cf1fdbd commit bbb9d72

File tree

2 files changed

+96
-98
lines changed

2 files changed

+96
-98
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,8 @@
77
using Rubberduck.Inspections.CodePathAnalysis.Extensions;
88
using System.Linq;
99
using Rubberduck.Inspections.Results;
10+
using Rubberduck.Parsing;
11+
using Rubberduck.Parsing.Grammar;
1012

1113
namespace Rubberduck.Inspections.Concrete
1214
{
@@ -21,7 +23,9 @@ public AssignmentNotUsedInspection(RubberduckParserState state, Walker walker)
2123

2224
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2325
{
24-
var variables = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable);
26+
var variables = State.DeclarationFinder
27+
.UserDeclarations(DeclarationType.Variable)
28+
.Where(d => !d.IsArray);
2529

2630
var nodes = new List<IdentifierReference>();
2731
foreach (var variable in variables)
@@ -32,6 +36,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3236
}
3337

3438
return nodes
39+
//.Where(n => !n.Context.TryGetChildContext<VBAParser.LExpressionContext>(out var lhs) || !lhs.TryGetChildContext<VBAParser.IndexExprContext>(out _))
3540
.Select(issue => new IdentifierReferenceInspectionResult(this, Description, State, issue))
3641
.ToList();
3742
}
Lines changed: 90 additions & 97 deletions
Original file line numberDiff line numberDiff line change
@@ -1,21 +1,78 @@
1-
using NUnit.Framework;
1+
using System.Collections.Generic;
2+
using NUnit.Framework;
23
using Rubberduck.Inspections.CodePathAnalysis;
34
using Rubberduck.Inspections.Concrete;
45
using RubberduckTests.Mocks;
56
using System.Linq;
67
using System.Threading;
8+
using Rubberduck.Parsing.Inspections.Abstract;
79

810
namespace RubberduckTests.Inspections
911
{
1012
[TestFixture]
1113
public class AssignmentNotUsedInspectionTests
1214
{
15+
private IEnumerable<IInspectionResult> GetInspectionResults(string code)
16+
{
17+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(code, out _);
18+
using (var state = MockParser.CreateAndParse(vbe.Object))
19+
{
20+
21+
var inspection = new AssignmentNotUsedInspection(state, new Walker());
22+
var inspector = InspectionsHelper.GetInspector(inspection);
23+
return inspector.FindIssuesAsync(state, CancellationToken.None).Result;
24+
}
25+
}
26+
27+
[Test]
28+
[Category("Inspections")]
29+
public void IgnoresExplicitArrays()
30+
{
31+
const string code = @"
32+
Sub Foo()
33+
Dim bar(1 To 10) As String
34+
bar(1) = 42
35+
End Sub
36+
";
37+
var results = GetInspectionResults(code);
38+
Assert.AreEqual(0, results.Count());
39+
}
40+
41+
[Test]
42+
[Category("Inspections")]
43+
public void IgnoresImplicitArrays()
44+
{
45+
const string code = @"
46+
Sub Foo()
47+
Dim bar As Variant
48+
bar(1) = ""Z""
49+
End Sub
50+
";
51+
var results = GetInspectionResults(code);
52+
Assert.AreEqual(0, results.Count());
53+
}
54+
55+
[Test]
56+
[Category("Inspections")]
57+
public void IgnoresImplicitReDimmedArray()
58+
{
59+
const string code = @"
60+
Sub test()
61+
Dim foo As Variant
62+
ReDim foo(1 To 10)
63+
foo(1) = 42
64+
End Sub
65+
";
66+
var results = GetInspectionResults(code);
67+
Assert.AreEqual(0, results.Count());
68+
}
69+
1370
[Test]
1471
[Category("Inspections")]
1572
public void MarksSequentialAssignments()
1673
{
17-
const string inputcode =
18-
@"Sub Foo()
74+
const string code = @"
75+
Sub Foo()
1976
Dim i As Integer
2077
i = 9
2178
i = 8
@@ -24,37 +81,21 @@ End Sub
2481
2582
Sub Bar(ByVal i As Integer)
2683
End Sub";
27-
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputcode, out _);
28-
using (var state = MockParser.CreateAndParse(vbe.Object))
29-
{
30-
31-
var inspection = new AssignmentNotUsedInspection(state, new Walker());
32-
var inspector = InspectionsHelper.GetInspector(inspection);
33-
var results = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
34-
35-
Assert.AreEqual(1, results.Count());
36-
}
84+
var results = GetInspectionResults(code);
85+
Assert.AreEqual(1, results.Count());
3786
}
3887

3988
[Test]
4089
[Category("Inspections")]
4190
public void MarksLastAssignmentInDeclarationBlock()
4291
{
43-
const string inputcode =
44-
@"Sub Foo()
92+
const string code = @"
93+
Sub Foo()
4594
Dim i As Integer
4695
i = 9
4796
End Sub";
48-
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputcode, out _);
49-
using (var state = MockParser.CreateAndParse(vbe.Object))
50-
{
51-
52-
var inspection = new AssignmentNotUsedInspection(state, new Walker());
53-
var inspector = InspectionsHelper.GetInspector(inspection);
54-
var results = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
55-
56-
Assert.AreEqual(1, results.Count());
57-
}
97+
var results = GetInspectionResults(code);
98+
Assert.AreEqual(1, results.Count());
5899
}
59100

60101
[Test]
@@ -63,8 +104,8 @@ Dim i As Integer
63104
// I just want feedback before I start mucking around that deep.
64105
public void DoesNotMarkLastAssignmentInNonDeclarationBlock()
65106
{
66-
const string inputcode =
67-
@"Sub Foo()
107+
const string code = @"
108+
Sub Foo()
68109
Dim i As Integer
69110
i = 0
70111
If i = 9 Then
@@ -73,120 +114,80 @@ Dim i As Integer
73114
i = 8
74115
End If
75116
End Sub";
76-
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputcode, out _);
77-
using (var state = MockParser.CreateAndParse(vbe.Object))
78-
{
79-
80-
var inspection = new AssignmentNotUsedInspection(state, new Walker());
81-
var inspector = InspectionsHelper.GetInspector(inspection);
82-
var results = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
83-
84-
Assert.AreEqual(0, results.Count());
85-
}
117+
var results = GetInspectionResults(code);
118+
Assert.AreEqual(0, results.Count());
86119
}
87120

88121
[Test]
89122
[Category("Inspections")]
90123
public void DoesNotMarkAssignmentWithReferenceAfter()
91124
{
92-
const string inputcode =
93-
@"Sub Foo()
125+
const string code = @"
126+
Sub Foo()
94127
Dim i As Integer
95128
i = 9
96129
Bar i
97130
End Sub
98131
99132
Sub Bar(ByVal i As Integer)
100133
End Sub";
101-
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputcode, out _);
102-
using (var state = MockParser.CreateAndParse(vbe.Object))
103-
{
104-
105-
var inspection = new AssignmentNotUsedInspection(state, new Walker());
106-
var inspector = InspectionsHelper.GetInspector(inspection);
107-
var results = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
108-
109-
Assert.AreEqual(0, results.Count());
110-
}
134+
var results = GetInspectionResults(code);
135+
Assert.AreEqual(0, results.Count());
111136
}
112137

113138
[Test]
114139
[Category("Inspections")]
115140
public void DoesNotMarkAssignment_UsedInForNext()
116141
{
117-
const string inputcode =
118-
@"Sub foo()
142+
const string code = @"
143+
Sub foo()
119144
Dim i As Integer
120145
i = 1
121146
For counter = i To 2
122147
Next
123148
End Sub";
124-
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputcode, out _);
125-
using (var state = MockParser.CreateAndParse(vbe.Object))
126-
{
127-
128-
var inspection = new AssignmentNotUsedInspection(state, new Walker());
129-
var inspector = InspectionsHelper.GetInspector(inspection);
130-
var results = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
131-
132-
Assert.AreEqual(0, results.Count());
133-
}
149+
var results = GetInspectionResults(code);
150+
Assert.AreEqual(0, results.Count());
134151
}
135152

136153
[Test]
137154
[Category("Inspections")]
138155
public void DoesNotMarkAssignment_UsedInWhileWend()
139156
{
140-
const string inputcode =
141-
@"Sub foo()
157+
const string code = @"
158+
Sub foo()
142159
Dim i As Integer
143160
i = 0
144161
145162
While i < 10
146163
i = i + 1
147164
Wend
148165
End Sub";
149-
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputcode, out _);
150-
using (var state = MockParser.CreateAndParse(vbe.Object))
151-
{
152-
153-
var inspection = new AssignmentNotUsedInspection(state, new Walker());
154-
var inspector = InspectionsHelper.GetInspector(inspection);
155-
var results = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
156-
157-
Assert.AreEqual(0, results.Count());
158-
}
166+
var results = GetInspectionResults(code);
167+
Assert.AreEqual(0, results.Count());
159168
}
160169

161170
[Test]
162171
[Category("Inspections")]
163172
public void DoesNotMarkAssignment_UsedInDoWhile()
164173
{
165-
const string inputcode =
166-
@"Sub foo()
174+
const string code = @"
175+
Sub foo()
167176
Dim i As Integer
168177
i = 0
169178
Do While i < 10
170179
Loop
171180
End Sub";
172-
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputcode, out _);
173-
using (var state = MockParser.CreateAndParse(vbe.Object))
174-
{
175-
176-
var inspection = new AssignmentNotUsedInspection(state, new Walker());
177-
var inspector = InspectionsHelper.GetInspector(inspection);
178-
var results = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
179-
180-
Assert.AreEqual(0, results.Count());
181-
}
181+
var results = GetInspectionResults(code);
182+
Assert.AreEqual(0, results.Count());
182183
}
183184

184185
[Test]
185186
[Category("Inspections")]
186187
public void DoesNotMarkAssignment_UsedInSelectCase()
187188
{
188-
const string inputcode =
189-
@"Sub foo()
189+
const string code = @"
190+
Sub foo()
190191
Dim i As Integer
191192
i = 0
192193
Select Case i
@@ -200,16 +201,8 @@ Case Else
200201
i = -1
201202
End Select
202203
End Sub";
203-
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputcode, out _);
204-
using (var state = MockParser.CreateAndParse(vbe.Object))
205-
{
206-
207-
var inspection = new AssignmentNotUsedInspection(state, new Walker());
208-
var inspector = InspectionsHelper.GetInspector(inspection);
209-
var results = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
210-
211-
Assert.AreEqual(0, results.Count());
212-
}
204+
var results = GetInspectionResults(code);
205+
Assert.AreEqual(0, results.Count());
213206
}
214207
}
215208
}

0 commit comments

Comments
 (0)