Skip to content

Commit 4eab52d

Browse files
committed
Tests for ignored inspections and ignore quick fix. A few bug fixes.
1 parent 02e39f3 commit 4eab52d

File tree

44 files changed

+2405
-148
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

44 files changed

+2405
-148
lines changed

RetailCoder.VBE/Inspections/EmptyStringLiteralInspection.cs

Lines changed: 1 addition & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,7 @@
11
using System.Collections.Generic;
22
using System.Linq;
33
using Antlr4.Runtime;
4-
using Microsoft.Vbe.Interop;
54
using Rubberduck.Parsing;
6-
using Rubberduck.Parsing.Annotations;
75
using Rubberduck.Parsing.VBA;
86
using Rubberduck.Parsing.Grammar;
97

@@ -29,33 +27,11 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2927
return new InspectionResultBase[] { };
3028
}
3129
return ParseTreeResults.EmptyStringLiterals
32-
.Where(s => !HasIgnoreEmptyStringLiteralAnnotations(s.ModuleName.Component, s.Context.Start.Line))
30+
.Where(s => !HasIgnoreAnnotation(s.ModuleName.Component, s.Context.Start.Line))
3331
.Select(context => new EmptyStringLiteralInspectionResult(this,
3432
new QualifiedContext<ParserRuleContext>(context.ModuleName, context.Context)));
3533
}
3634

37-
private bool HasIgnoreEmptyStringLiteralAnnotations(VBComponent component, int line)
38-
{
39-
var annotations = State.GetModuleAnnotations(component).ToList();
40-
41-
if (State.GetModuleAnnotations(component) == null)
42-
{
43-
return false;
44-
}
45-
46-
// VBE 1-based indexing
47-
for (var i = line - 1; i >= 1; i--)
48-
{
49-
var annotation = annotations.SingleOrDefault(a => a.QualifiedSelection.Selection.StartLine == i) as IgnoreAnnotation;
50-
if (annotation != null && annotation.InspectionNames.Contains(AnnotationName))
51-
{
52-
return true;
53-
}
54-
}
55-
56-
return false;
57-
}
58-
5935
public class EmptyStringLiteralListener : VBAParserBaseListener
6036
{
6137
private readonly IList<VBAParser.LiteralExpressionContext> _contexts = new List<VBAParser.LiteralExpressionContext>();

RetailCoder.VBE/Inspections/InspectionBase.cs

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,8 @@
11
using System;
22
using System.Collections.Generic;
33
using System.Linq;
4+
using Microsoft.Vbe.Interop;
5+
using Rubberduck.Parsing.Annotations;
46
using Rubberduck.Parsing.Symbols;
57
using Rubberduck.Parsing.VBA;
68

@@ -81,6 +83,28 @@ protected virtual IEnumerable<Declaration> BuiltInDeclarations
8183
get { return State.AllDeclarations.Where(declaration => declaration.IsBuiltIn); }
8284
}
8385

86+
protected bool HasIgnoreAnnotation(VBComponent component, int line)
87+
{
88+
var annotations = State.GetModuleAnnotations(component).ToList();
89+
90+
if (State.GetModuleAnnotations(component) == null)
91+
{
92+
return false;
93+
}
94+
95+
// VBE 1-based indexing
96+
for (var i = line - 1; i >= 1; i--)
97+
{
98+
var annotation = annotations.SingleOrDefault(a => a.QualifiedSelection.Selection.StartLine == i) as IgnoreAnnotation;
99+
if (annotation != null && annotation.InspectionNames.Contains(AnnotationName))
100+
{
101+
return true;
102+
}
103+
}
104+
105+
return false;
106+
}
107+
84108
/// <summary>
85109
/// Gets all user declarations in the parser state without an @Ignore annotation for this inspection.
86110
/// </summary>

RetailCoder.VBE/Inspections/MultilineParameterInspectionResult.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ public MultilineParameterInspectionResult(IInspection inspection, Declaration ta
1515
_quickFixes = new CodeInspectionQuickFix[]
1616
{
1717
new MakeSingleLineParameterQuickFix(Context, QualifiedSelection),
18-
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName)
18+
new IgnoreOnceQuickFix(Target.ParentDeclaration.Context, Target.ParentDeclaration.QualifiedSelection, Inspection.AnnotationName)
1919
};
2020
}
2121

RetailCoder.VBE/Inspections/ObsoleteCallStatementInspection.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
using System.Collections.Generic;
2+
using System.Linq;
23
using Rubberduck.Parsing;
34
using Rubberduck.Parsing.Grammar;
45
using Rubberduck.Parsing.VBA;
@@ -26,7 +27,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2627

2728
var results = new List<ObsoleteCallStatementUsageInspectionResult>();
2829

29-
foreach (var context in ParseTreeResults.ObsoleteCallContexts)
30+
foreach (var context in ParseTreeResults.ObsoleteCallContexts.Where(o => !HasIgnoreAnnotation(o.ModuleName.Component, o.Context.Start.Line)))
3031
{
3132
var lines = context.ModuleName.Component.CodeModule.Lines[
3233
context.Context.Start.Line, context.Context.Stop.Line - context.Context.Start.Line + 1];

RetailCoder.VBE/Inspections/ObsoleteCommentSyntaxInspection.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,8 @@ public ObsoleteCommentSyntaxInspection(RubberduckParserState state)
2121

2222
public override IEnumerable<InspectionResultBase> GetInspectionResults()
2323
{
24-
return State.AllComments.Where(comment => comment.Marker == Tokens.Rem)
24+
return State.AllComments.Where(comment => comment.Marker == Tokens.Rem &&
25+
!HasIgnoreAnnotation(comment.QualifiedSelection.QualifiedName.Component, comment.QualifiedSelection.Selection.StartLine))
2526
.Select(comment => new ObsoleteCommentSyntaxInspectionResult(this, comment));
2627
}
2728
}

RetailCoder.VBE/Inspections/ObsoleteLetStatementInspection.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -25,8 +25,9 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2525
{
2626
return new InspectionResultBase[] { };
2727
}
28-
return ParseTreeResults.ObsoleteLetContexts.Select(context =>
29-
new ObsoleteLetStatementUsageInspectionResult(this, new QualifiedContext<ParserRuleContext>(context.ModuleName, context.Context)));
28+
return ParseTreeResults.ObsoleteLetContexts
29+
.Where(o => !HasIgnoreAnnotation(o.ModuleName.Component, o.Context.Start.Line))
30+
.Select(context => new ObsoleteLetStatementUsageInspectionResult(this, new QualifiedContext<ParserRuleContext>(context.ModuleName, context.Context)));
3031
}
3132

3233
public class ObsoleteLetStatementListener : VBAParserBaseListener

RetailCoder.VBE/Inspections/UntypedFunctionUsageInspection.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,8 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
4848
item.Scope.StartsWith("VBE7.DLL;"));
4949

5050
return declarations.SelectMany(declaration => declaration.References
51-
.Where(item => _tokens.Contains(item.IdentifierName))
51+
.Where(item => _tokens.Contains(item.IdentifierName) &&
52+
!HasIgnoreAnnotation(item.QualifiedModuleName.Component, item.Selection.StartLine))
5253
.Select(item => new UntypedFunctionUsageInspectionResult(this, item)));
5354
}
5455
}

RubberduckTests/Inspections/AssignedByValParameterInspectionTests.cs

Lines changed: 63 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -119,6 +119,33 @@ public void AssignedByValParameter_DoesNotReturnResult()
119119
Assert.AreEqual(0, inspectionResults.Count());
120120
}
121121

122+
[TestMethod]
123+
[TestCategory("Inspections")]
124+
public void AssignedByValParameter_Ignored_DoesNotReturnResult_Sub()
125+
{
126+
const string inputCode =
127+
@"'@Ignore AssignedByValParameter
128+
Public Sub Foo(ByVal arg1 As String)
129+
Let arg1 = ""test""
130+
End Sub";
131+
132+
//Arrange
133+
var builder = new MockVbeBuilder();
134+
VBComponent component;
135+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
136+
var mockHost = new Mock<IHostApplication>();
137+
mockHost.SetupAllProperties();
138+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object, new Mock<ISinks>().Object));
139+
140+
parser.Parse(new CancellationTokenSource());
141+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
142+
143+
var inspection = new AssignedByValParameterInspection(parser.State);
144+
var inspectionResults = inspection.GetInspectionResults();
145+
146+
Assert.IsFalse(inspectionResults.Any());
147+
}
148+
122149
[TestMethod]
123150
[TestCategory("Inspections")]
124151
public void AssignedByValParameter_ReturnsResult_SomeAssignedByValParams()
@@ -183,6 +210,42 @@ public void AssignedByValParameter_QuickFixWorks()
183210
Assert.AreEqual(expectedCode, module.Lines());
184211
}
185212

213+
[TestMethod]
214+
[TestCategory("Inspections")]
215+
public void AssignedByValParameter_IgnoreQuickFixWorks()
216+
{
217+
const string inputCode =
218+
@"Public Sub Foo(ByVal arg1 As String)
219+
Let arg1 = ""test""
220+
End Sub";
221+
222+
const string expectedCode =
223+
@"'@Ignore AssignedByValParameter
224+
Public Sub Foo(ByVal arg1 As String)
225+
Let arg1 = ""test""
226+
End Sub";
227+
228+
//Arrange
229+
var builder = new MockVbeBuilder();
230+
VBComponent component;
231+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
232+
var project = vbe.Object.VBProjects.Item(0);
233+
var module = project.VBComponents.Item(0).CodeModule;
234+
var mockHost = new Mock<IHostApplication>();
235+
mockHost.SetupAllProperties();
236+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object, new Mock<ISinks>().Object));
237+
238+
parser.Parse(new CancellationTokenSource());
239+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
240+
241+
var inspection = new AssignedByValParameterInspection(parser.State);
242+
var inspectionResults = inspection.GetInspectionResults();
243+
244+
inspectionResults.First().QuickFixes.Single(s => s is IgnoreOnceQuickFix).Fix();
245+
246+
Assert.AreEqual(expectedCode, module.Lines());
247+
}
248+
186249
[TestMethod]
187250
[TestCategory("Inspections")]
188251
public void InspectionType()

RubberduckTests/Inspections/ConstantNotUsedInspectionTests.cs

Lines changed: 69 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -70,12 +70,14 @@ public void ConstantNotUsed_ReturnsResult_MultipleConsts()
7070

7171
[TestMethod]
7272
[TestCategory("Inspections")]
73-
public void GivenReferencedConstant_ReturnsNoInspectionResult()
73+
public void ConstantNotUsed_ReturnsResult_UnusedConstant()
7474
{
7575
const string inputCode =
7676
@"Public Sub Foo()
7777
Const const1 As Integer = 9
7878
Goo const1
79+
80+
Const const2 As String = ""test""
7981
End Sub
8082
8183
Public Sub Goo(ByVal arg1 As Integer)
@@ -95,19 +97,17 @@ Public Sub Goo(ByVal arg1 As Integer)
9597
var inspection = new ConstantNotUsedInspection(parser.State);
9698
var inspectionResults = inspection.GetInspectionResults();
9799

98-
Assert.AreEqual(0, inspectionResults.Count());
100+
Assert.AreEqual(1, inspectionResults.Count());
99101
}
100102

101103
[TestMethod]
102104
[TestCategory("Inspections")]
103-
public void GivenConstantNotUsed_ReturnsResultForUnusedConstant()
105+
public void ConstantNotUsed_DoesNotReturnResult()
104106
{
105107
const string inputCode =
106108
@"Public Sub Foo()
107109
Const const1 As Integer = 9
108110
Goo const1
109-
110-
Const const2 As String = ""test""
111111
End Sub
112112
113113
Public Sub Goo(ByVal arg1 As Integer)
@@ -127,7 +127,34 @@ Public Sub Goo(ByVal arg1 As Integer)
127127
var inspection = new ConstantNotUsedInspection(parser.State);
128128
var inspectionResults = inspection.GetInspectionResults();
129129

130-
Assert.AreEqual(1, inspectionResults.Count());
130+
Assert.AreEqual(0, inspectionResults.Count());
131+
}
132+
133+
[TestMethod]
134+
[TestCategory("Inspections")]
135+
public void ConstantNotUsed_Ignored_DoesNotReturnResult()
136+
{
137+
const string inputCode =
138+
@"Public Sub Foo()
139+
'@Ignore ConstantNotUsed
140+
Const const1 As Integer = 9
141+
End Sub";
142+
143+
//Arrange
144+
var builder = new MockVbeBuilder();
145+
VBComponent component;
146+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
147+
var mockHost = new Mock<IHostApplication>();
148+
mockHost.SetupAllProperties();
149+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object, new Mock<ISinks>().Object));
150+
151+
parser.Parse(new CancellationTokenSource());
152+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
153+
154+
var inspection = new ConstantNotUsedInspection(parser.State);
155+
var inspectionResults = inspection.GetInspectionResults();
156+
157+
Assert.IsFalse(inspectionResults.Any());
131158
}
132159

133160
[TestMethod]
@@ -164,6 +191,42 @@ public void ConstantNotUsed_QuickFixWorks()
164191
Assert.AreEqual(expectedCode, module.Lines());
165192
}
166193

194+
[TestMethod]
195+
[TestCategory("Inspections")]
196+
public void ConstantNotUsed_IgnoreQuickFixWorks()
197+
{
198+
const string inputCode =
199+
@"Public Sub Foo()
200+
Const const1 As Integer = 9
201+
End Sub";
202+
203+
const string expectedCode =
204+
@"Public Sub Foo()
205+
'@Ignore ConstantNotUsed
206+
Const const1 As Integer = 9
207+
End Sub";
208+
209+
//Arrange
210+
var builder = new MockVbeBuilder();
211+
VBComponent component;
212+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
213+
var project = vbe.Object.VBProjects.Item(0);
214+
var module = project.VBComponents.Item(0).CodeModule;
215+
var mockHost = new Mock<IHostApplication>();
216+
mockHost.SetupAllProperties();
217+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object, new Mock<ISinks>().Object));
218+
219+
parser.Parse(new CancellationTokenSource());
220+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
221+
222+
var inspection = new ConstantNotUsedInspection(parser.State);
223+
var inspectionResults = inspection.GetInspectionResults();
224+
225+
inspectionResults.First().QuickFixes.Single(s => s is IgnoreOnceQuickFix).Fix();
226+
227+
Assert.AreEqual(expectedCode, module.Lines());
228+
}
229+
167230
[TestMethod]
168231
[TestCategory("Inspections")]
169232
public void InspectionType()

RubberduckTests/Inspections/DefaultProjectNameInspectionTests.cs

Lines changed: 26 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -18,12 +18,10 @@ public class DefaultProjectNameInspectionTests
1818
[TestCategory("Inspections")]
1919
public void DefaultProjectName_ReturnsResult()
2020
{
21-
const string inputCode = @"";
22-
2321
//Arrange
2422
var builder = new MockVbeBuilder();
2523
var project = builder.ProjectBuilder("VBAProject", vbext_ProjectProtection.vbext_pp_none)
26-
.AddComponent("Class1", vbext_ComponentType.vbext_ct_ClassModule, inputCode)
24+
.AddComponent("Class1", vbext_ComponentType.vbext_ct_ClassModule, string.Empty)
2725
.Build();
2826
var vbe = builder.AddProject(project).Build();
2927

@@ -44,12 +42,10 @@ public void DefaultProjectName_ReturnsResult()
4442
[TestCategory("Inspections")]
4543
public void DefaultProjectName_DoesNotReturnResult()
4644
{
47-
const string inputCode = @"";
48-
4945
//Arrange
5046
var builder = new MockVbeBuilder();
5147
var project = builder.ProjectBuilder("TestProject", vbext_ProjectProtection.vbext_pp_none)
52-
.AddComponent("Class1", vbext_ComponentType.vbext_ct_ClassModule, inputCode)
48+
.AddComponent("Class1", vbext_ComponentType.vbext_ct_ClassModule, string.Empty)
5349
.Build();
5450
var vbe = builder.AddProject(project).Build();
5551

@@ -66,6 +62,30 @@ public void DefaultProjectName_DoesNotReturnResult()
6662
Assert.AreEqual(0, inspectionResults.Count());
6763
}
6864

65+
[TestMethod]
66+
[TestCategory("Inspections")]
67+
public void DefaultProjectName_NoIgnoreQuickFix()
68+
{
69+
//Arrange
70+
var builder = new MockVbeBuilder();
71+
var project = builder.ProjectBuilder("VBAProject", vbext_ProjectProtection.vbext_pp_none)
72+
.AddComponent("Class1", vbext_ComponentType.vbext_ct_ClassModule, string.Empty)
73+
.Build();
74+
var vbe = builder.AddProject(project).Build();
75+
76+
var mockHost = new Mock<IHostApplication>();
77+
mockHost.SetupAllProperties();
78+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object, new Mock<ISinks>().Object));
79+
80+
parser.Parse(new CancellationTokenSource());
81+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
82+
83+
var inspection = new DefaultProjectNameInspection(parser.State);
84+
var inspectionResults = inspection.GetInspectionResults();
85+
86+
Assert.IsFalse(inspectionResults.ElementAt(0).QuickFixes.Any(q => q is IgnoreOnceQuickFix));
87+
}
88+
6989
[TestMethod]
7090
[TestCategory("Inspections")]
7191
public void InspectionType()

0 commit comments

Comments
 (0)