Skip to content

Commit 15d6320

Browse files
committed
Make ObsoleteCallStatementInspection more precise
Also removes the use of a CodeModule.
1 parent 117f00f commit 15d6320

File tree

5 files changed

+35
-20
lines changed

5 files changed

+35
-20
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallStatementInspection.cs

Lines changed: 8 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -40,13 +40,10 @@ namespace Rubberduck.Inspections.Concrete
4040
/// </example>
4141
public sealed class ObsoleteCallStatementInspection : ParseTreeInspectionBase
4242
{
43-
private readonly IProjectsProvider _projectsProvider;
44-
45-
public ObsoleteCallStatementInspection(IDeclarationFinderProvider declarationFinderProvider, IProjectsProvider projectsProvider)
43+
public ObsoleteCallStatementInspection(IDeclarationFinderProvider declarationFinderProvider)
4644
: base(declarationFinderProvider)
4745
{
4846
Listener = new ObsoleteCallStatementListener();
49-
_projectsProvider = projectsProvider;
5047
}
5148

5249
public override IInspectionListener Listener { get; }
@@ -57,23 +54,19 @@ protected override string ResultDescription(QualifiedContext<ParserRuleContext>
5754

5855
protected override bool IsResultContext(QualifiedContext<ParserRuleContext> context)
5956
{
60-
//FIXME At least use a parse tree here instead of the COM API.
61-
string lines;
62-
var component = _projectsProvider.Component(context.ModuleName);
63-
using (var module = component.CodeModule)
57+
if (!context.Context.TryGetFollowingContext(out VBAParser.IndividualNonEOFEndOfStatementContext followingEndOfStatement)
58+
|| followingEndOfStatement.COLON() == null)
6459
{
65-
lines = module.GetLines(context.Context.Start.Line,
66-
context.Context.Stop.Line - context.Context.Start.Line + 1);
60+
return true;
6761
}
6862

69-
var stringStrippedLines = string.Join(string.Empty, lines).StripStringLiterals();
70-
71-
if (stringStrippedLines.HasComment(out var commentIndex))
63+
if (!context.Context.TryGetPrecedingContext(out VBAParser.IndividualNonEOFEndOfStatementContext precedingEndOfStatement)
64+
|| precedingEndOfStatement.endOfLine() == null)
7265
{
73-
stringStrippedLines = stringStrippedLines.Remove(commentIndex);
66+
return true;
7467
}
7568

76-
return !stringStrippedLines.Contains(":");
69+
return false;
7770
}
7871

7972
public class ObsoleteCallStatementListener : InspectionListenerBase

RubberduckTests/Inspections/ObsoleteCallStatementInspectionTests.cs

Lines changed: 24 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -43,6 +43,28 @@ public void ObsoleteCallStatement_DoesNotReturnResult_InstructionSeparator()
4343
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
4444
}
4545

46+
[Test]
47+
[Category("Inspections")]
48+
public void ObsoleteCallStatement_ReturnsResult_LabelInFront()
49+
{
50+
const string inputCode =
51+
@"Sub Foo()
52+
Foo: Call Foo
53+
End Sub";
54+
Assert.AreEqual(1, InspectionResultsForStandardModule(inputCode).Count());
55+
}
56+
57+
[Test]
58+
[Category("Inspections")]
59+
public void ObsoleteCallStatement_ReturnsResult_LabelInFrontWithSeparator()
60+
{
61+
const string inputCode =
62+
@"Sub Foo()
63+
Foo: Call Foo : Foo
64+
End Sub";
65+
Assert.AreEqual(1, InspectionResultsForStandardModule(inputCode).Count());
66+
}
67+
4668
[Test]
4769
[Category("Inspections")]
4870
public void ObsoleteCallStatement_ReturnsResult_ColonInComment()
@@ -111,14 +133,14 @@ Call Foo
111133
[Category("Inspections")]
112134
public void InspectionName()
113135
{
114-
var inspection = new ObsoleteCallStatementInspection(null, null);
136+
var inspection = new ObsoleteCallStatementInspection(null);
115137

116138
Assert.AreEqual(nameof(ObsoleteCallStatementInspection), inspection.Name);
117139
}
118140

119141
protected override IInspection InspectionUnderTest(RubberduckParserState state)
120142
{
121-
return new ObsoleteCallStatementInspection(state, state.ProjectsProvider);
143+
return new ObsoleteCallStatementInspection(state);
122144
}
123145
}
124146
}

RubberduckTests/Inspections/RedundantOptionInspectionTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ public void RedundantOptionInspection_Ignored_DoesNotReturnResult()
3232
using (var state = MockParser.CreateAndParse(vbe.Object))
3333
{
3434

35-
var inspection = new ObsoleteCallStatementInspection(state, state.ProjectsProvider);
35+
var inspection = new ObsoleteCallStatementInspection(state);
3636
var inspector = InspectionsHelper.GetInspector(inspection);
3737
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
3838

RubberduckTests/QuickFixes/IgnoreOnceQuickFixTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -465,7 +465,7 @@ Sub Goo(arg1 As Integer, arg1 As String)
465465
Call Foo
466466
End Sub";
467467

468-
var actualCode = ApplyIgnoreOnceToAllResults(inputCode, state => new ObsoleteCallStatementInspection(state, state.ProjectsProvider), TestStandardModuleVbeSetup);
468+
var actualCode = ApplyIgnoreOnceToAllResults(inputCode, state => new ObsoleteCallStatementInspection(state), TestStandardModuleVbeSetup);
469469
Assert.AreEqual(expectedCode, actualCode);
470470
}
471471

RubberduckTests/QuickFixes/RemoveExplicitCallStatementQuickFixTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ Sub Goo(arg1 As Integer, arg1 As String)
3232
Foo
3333
End Sub";
3434

35-
var actualCode = ApplyQuickFixToAllInspectionResults(inputCode, state => new ObsoleteCallStatementInspection(state, state.ProjectsProvider));
35+
var actualCode = ApplyQuickFixToAllInspectionResults(inputCode, state => new ObsoleteCallStatementInspection(state));
3636
Assert.AreEqual(expectedCode, actualCode);
3737
}
3838

0 commit comments

Comments
 (0)