Skip to content

Commit 3c002ee

Browse files
committed
Add support for VB6 versions of Len and LenB, simplify inspection, add tests.
1 parent 5f06ac2 commit 3c002ee

File tree

2 files changed

+84
-37
lines changed

2 files changed

+84
-37
lines changed
Lines changed: 18 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,8 @@
11
using System.Collections.Generic;
22
using System.Diagnostics.CodeAnalysis;
33
using System.Linq;
4-
using Antlr4.Runtime;
54
using Rubberduck.Inspections.Abstract;
65
using Rubberduck.Inspections.Results;
7-
using Rubberduck.Parsing;
86
using Rubberduck.Parsing.Inspections.Abstract;
97
using Rubberduck.Resources.Inspections;
108
using Rubberduck.Parsing.Symbols;
@@ -18,6 +16,15 @@ public sealed class UnassignedVariableUsageInspection : InspectionBase
1816
public UnassignedVariableUsageInspection(RubberduckParserState state)
1917
: base(state) { }
2018

19+
//See https://github.com/rubberduck-vba/Rubberduck/issues/2010 for why these are being excluded.
20+
private static readonly List<string> IgnoredFunctions = new List<string>
21+
{
22+
"VBE7.DLL;VBA.Strings.Len",
23+
"VBE7.DLL;VBA.Strings.LenB",
24+
"VBA6.DLL;VBA.Strings.Len",
25+
"VBA6.DLL;VBA.Strings.LenB"
26+
};
27+
2128
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2229
{
2330
var declarations = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
@@ -27,42 +34,16 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2734
&& !declaration.IsSelfAssigned
2835
&& !declaration.References.Any(reference => reference.IsAssignment));
2936

30-
//See https://github.com/rubberduck-vba/Rubberduck/issues/2010 for why these are being excluded.
31-
//TODO: These need to be modified to correctly work in VB6.
32-
var lenFunction = BuiltInDeclarations.SingleOrDefault(s => s.DeclarationType == DeclarationType.Function && s.Scope.Equals("VBE7.DLL;VBA.Strings.Len"));
33-
var lenbFunction = BuiltInDeclarations.SingleOrDefault(s => s.DeclarationType == DeclarationType.Function && s.Scope.Equals("VBE7.DLL;VBA.Strings.LenB"));
37+
var excludedDeclarations = BuiltInDeclarations.Where(decl => IgnoredFunctions.Contains(decl.QualifiedName.ToString())).ToList();
3438

35-
return declarations.Where(d => d.References.Any() &&
36-
!DeclarationReferencesContainsReference(lenFunction, d) &&
37-
!DeclarationReferencesContainsReference(lenbFunction, d))
38-
.SelectMany(d => d.References)
39-
.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
40-
.Select(r => new IdentifierReferenceInspectionResult(this,
41-
string.Format(InspectionResults.UnassignedVariableUsageInspection, r.IdentifierName),
42-
State,
43-
r)).ToList();
44-
}
45-
46-
private bool DeclarationReferencesContainsReference(Declaration parentDeclaration, Declaration target)
47-
{
48-
if (parentDeclaration == null)
49-
{
50-
return false;
51-
}
52-
53-
foreach (var targetReference in target.References)
54-
{
55-
foreach (var reference in parentDeclaration.References)
56-
{
57-
var context = (ParserRuleContext) reference.Context.Parent;
58-
if (context.GetSelection().Contains(targetReference.Selection))
59-
{
60-
return true;
61-
}
62-
}
63-
}
64-
65-
return false;
39+
return declarations.Except(excludedDeclarations)
40+
.Where(d => d.References.Any())
41+
.SelectMany(d => d.References)
42+
.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
43+
.Select(r => new IdentifierReferenceInspectionResult(this,
44+
string.Format(InspectionResults.UnassignedVariableUsageInspection, r.IdentifierName),
45+
State,
46+
r)).ToList();
6647
}
6748
}
6849
}

RubberduckTests/Inspections/UnassignedVariableUsageInspectionTests.cs

Lines changed: 66 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -112,6 +112,30 @@ Dim bb As Boolean
112112
}
113113
}
114114

115+
[Test]
116+
[Category("Inspections")]
117+
public void UnassignedVariableUsage_Ignored_DoesNotReturnResultMultipleIgnores()
118+
{
119+
const string inputCode =
120+
@"Sub Foo()
121+
Dim b As Boolean
122+
Dim bb As Boolean
123+
124+
'@Ignore UnassignedVariableUsage, VariableNotAssigned
125+
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+
}
137+
}
138+
115139
[Test]
116140
[Category("Inspections")]
117141
public void UnassignedVariableUsage_NoResultIfNoReferences()
@@ -132,6 +156,48 @@ Dim foo
132156
}
133157
}
134158

159+
[Test]
160+
[Category("Inspections")]
161+
public void UnassignedVariableUsage_NoResultForLenFunction()
162+
{
163+
const string inputCode =
164+
@"Sub DoSomething()
165+
Dim foo As LongPtr
166+
Debug.Print Len(foo)
167+
End Sub";
168+
169+
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
170+
using (var state = MockParser.CreateAndParse(vbe.Object))
171+
{
172+
173+
var inspection = new UnassignedVariableUsageInspection(state);
174+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
175+
176+
Assert.IsFalse(inspectionResults.Any());
177+
}
178+
}
179+
180+
[Test]
181+
[Category("Inspections")]
182+
public void UnassignedVariableUsage_NoResultForLenBFunction()
183+
{
184+
const string inputCode =
185+
@"Sub DoSomething()
186+
Dim foo As LongPtr
187+
Debug.Print LenB(foo)
188+
End Sub";
189+
190+
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
191+
using (var state = MockParser.CreateAndParse(vbe.Object))
192+
{
193+
194+
var inspection = new UnassignedVariableUsageInspection(state);
195+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
196+
197+
Assert.IsFalse(inspectionResults.Any());
198+
}
199+
}
200+
135201
[Test]
136202
[Category("Inspections")]
137203
public void InspectionName()

0 commit comments

Comments
 (0)