Skip to content

Commit 7f35af8

Browse files
committed
Introduce IgnoreInModuleQuickFix
This adds an IgnoreModule annotation for the inspection corresponding to the result.
1 parent eb66ed9 commit 7f35af8

File tree

7 files changed

+258
-3
lines changed

7 files changed

+258
-3
lines changed
Lines changed: 103 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,103 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.CodeAnalysis.Inspections;
4+
using Rubberduck.CodeAnalysis.Inspections.Attributes;
5+
using Rubberduck.CodeAnalysis.QuickFixes.Abstract;
6+
using Rubberduck.Parsing.Annotations;
7+
using Rubberduck.Parsing.Rewriter;
8+
using Rubberduck.Parsing.Symbols;
9+
using Rubberduck.Parsing.VBA;
10+
11+
namespace Rubberduck.CodeAnalysis.QuickFixes.Concrete
12+
{
13+
/// <summary>
14+
/// Adds an '@IgnoreModule annotation to ignore a inspection results for a specific inspection inside a whole module. Applicable to all inspections whose results can be annotated in a module.
15+
/// </summary>
16+
/// <canfix procedure="false" module="false" project="false" />
17+
/// <example>
18+
/// <before>
19+
/// <![CDATA[
20+
/// Public Sub DoSomething()
21+
/// Dim value As Long
22+
/// Dim bar As Long
23+
/// value = 42
24+
/// bar = 23
25+
/// Debug.Print 42
26+
/// End Sub
27+
/// ]]>
28+
/// </before>
29+
/// <after>
30+
/// <![CDATA[
31+
/// '@IgnoreModule VariableNotUsed
32+
/// Public Sub DoSomething()
33+
/// Dim value As Long
34+
/// Dim bar As Long
35+
/// value = 42
36+
/// bar = 23
37+
/// Debug.Print 42
38+
/// End Sub
39+
/// ]]>
40+
/// </after>
41+
/// </example>
42+
internal sealed class IgnoreInModuleQuickFix : QuickFixBase
43+
{
44+
private readonly RubberduckParserState _state;
45+
private readonly IAnnotationUpdater _annotationUpdater;
46+
47+
public IgnoreInModuleQuickFix(IAnnotationUpdater annotationUpdater, RubberduckParserState state, IEnumerable<IInspection> inspections)
48+
: base(inspections.Select(s => s.GetType()).Where(i => i.CustomAttributes.All(a => a.AttributeType != typeof(CannotAnnotateAttribute))).ToArray())
49+
{
50+
_state = state;
51+
_annotationUpdater = annotationUpdater;
52+
}
53+
54+
public override bool CanFixInProcedure => false;
55+
public override bool CanFixInModule => true;
56+
public override bool CanFixInProject => true;
57+
public override bool CanFixAll => true;
58+
59+
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
60+
{
61+
var module = result.Target.QualifiedModuleName;
62+
var moduleDeclaration = _state.DeclarationFinder.Members(module, DeclarationType.Module)
63+
.FirstOrDefault();
64+
65+
if (moduleDeclaration == null)
66+
{
67+
return;
68+
}
69+
70+
var existingIgnoreModuleAnnotation = moduleDeclaration.Annotations
71+
.FirstOrDefault(pta => pta.Annotation is IgnoreModuleAnnotation);
72+
73+
var annotationType = new IgnoreModuleAnnotation();
74+
if (existingIgnoreModuleAnnotation != null)
75+
{
76+
var annotationValues = existingIgnoreModuleAnnotation.AnnotationArguments.ToList();
77+
78+
if (annotationValues.Contains(result.Inspection.AnnotationName))
79+
{
80+
return;
81+
}
82+
83+
annotationValues.Insert(0, result.Inspection.AnnotationName);
84+
_annotationUpdater.UpdateAnnotation(rewriteSession, existingIgnoreModuleAnnotation, annotationType, annotationValues);
85+
}
86+
else
87+
{
88+
var newModuleText = rewriteSession.CheckOutModuleRewriter(module).GetText();
89+
var ignoreModuleText = $"'{ParseTreeAnnotation.ANNOTATION_MARKER}{annotationType.Name}";
90+
if (newModuleText.Contains(ignoreModuleText))
91+
{
92+
//Most probably, we have added this already in another invocation on the same rewrite session.
93+
return;
94+
}
95+
96+
var annotationValues = new List<string> { result.Inspection.AnnotationName };
97+
_annotationUpdater.AddAnnotation(rewriteSession, moduleDeclaration, annotationType, annotationValues);
98+
}
99+
}
100+
101+
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.IgnoreInModuleQuickFix;
102+
}
103+
}

Rubberduck.CodeAnalysis/QuickFixes/Concrete/IgnoreOnceQuickFix.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,7 @@ public IgnoreOnceQuickFix(IAnnotationUpdater annotationUpdater, RubberduckParser
5151
public override bool CanFixInProcedure => false;
5252
public override bool CanFixInModule => false;
5353
public override bool CanFixInProject => false;
54+
public override bool CanFixAll => false;
5455

5556
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
5657
{
@@ -90,8 +91,7 @@ private void FixModule(IInspectionResult result, IRewriteSession rewriteSession)
9091
{
9192
var moduleDeclaration = result.Target;
9293
var existingIgnoreModuleAnnotation = moduleDeclaration.Annotations
93-
.Where(pta => pta.Annotation is IgnoreModuleAnnotation)
94-
.FirstOrDefault();
94+
.FirstOrDefault(pta => pta.Annotation is IgnoreModuleAnnotation);
9595

9696
var annotationType = new IgnoreModuleAnnotation();
9797
if (existingIgnoreModuleAnnotation != null)

Rubberduck.Core/UI/Inspections/QuickFixImageSourceConverter.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,9 @@ public class QuickFixImageSourceConverter : ImageSourceConverter
1212

1313
public override object Convert(object value, Type targetType, object parameter, CultureInfo culture)
1414
{
15-
if (value != null && value.GetType().Name.Equals("IgnoreOnceQuickFix"))
15+
if (value != null
16+
&& (value.GetType().Name.Equals("IgnoreOnceQuickFix")
17+
|| value.GetType().Name.Equals("IgnoreInModuleQuickFix")))
1618
{
1719
return IgnoreOnceIcon;
1820
}

Rubberduck.Resources/Inspections/QuickFixes.Designer.cs

Lines changed: 9 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Resources/Inspections/QuickFixes.de.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -297,4 +297,7 @@
297297
<data name="ExpandDefaultMemberQuickFix" xml:space="preserve">
298298
<value>Füge einen expliziten Zugriff auf den Standardmember ein</value>
299299
</data>
300+
<data name="IgnoreInModuleQuickFix" xml:space="preserve">
301+
<value>In Modul ignorieren</value>
302+
</data>
300303
</root>

Rubberduck.Resources/Inspections/QuickFixes.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -297,4 +297,7 @@
297297
<data name="ExpandDefaultMemberQuickFix" xml:space="preserve">
298298
<value>Make default member access explicit</value>
299299
</data>
300+
<data name="IgnoreInModuleQuickFix" xml:space="preserve">
301+
<value>Ignore in module</value>
302+
</data>
300303
</root>
Lines changed: 135 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,135 @@
1+
using System.Collections.Generic;
2+
using NUnit.Framework;
3+
using Rubberduck.CodeAnalysis.Inspections;
4+
using Rubberduck.CodeAnalysis.Inspections.Concrete;
5+
using Rubberduck.CodeAnalysis.QuickFixes;
6+
using Rubberduck.CodeAnalysis.QuickFixes.Concrete;
7+
using Rubberduck.Parsing.VBA;
8+
9+
namespace RubberduckTests.QuickFixes
10+
{
11+
[TestFixture]
12+
public class IgnoreInModuleQuickFixTests : QuickFixTestBase
13+
{
14+
[Test]
15+
[Category("QuickFixes")]
16+
public void NoIgnoreModule_AddsNewOne()
17+
{
18+
var inputCode =
19+
@"
20+
Public Sub DoSomething()
21+
Dim value As Long
22+
Dim bar As Long
23+
value = 42
24+
bar = 23
25+
Debug.Print 42
26+
End Sub";
27+
28+
var expectedCode =
29+
@"'@IgnoreModule VariableNotUsed
30+
31+
Public Sub DoSomething()
32+
Dim value As Long
33+
Dim bar As Long
34+
value = 42
35+
bar = 23
36+
Debug.Print 42
37+
End Sub";
38+
39+
var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new VariableNotUsedInspection(state));
40+
Assert.AreEqual(expectedCode, actualCode);
41+
}
42+
43+
[Test]
44+
[Category("QuickFixes")]
45+
public void IgnoreModuleAlreadyThere_InspectionNotIgnoredYet_AddsNewArgument()
46+
{
47+
var inputCode =
48+
@"'@IgnoreModule AssignmentNotUsed
49+
Public Sub DoSomething()
50+
Dim value As Long
51+
Dim bar As Long
52+
value = 42
53+
bar = 23
54+
Debug.Print 42
55+
End Sub";
56+
57+
var expectedCode =
58+
@"'@IgnoreModule VariableNotUsed, AssignmentNotUsed
59+
Public Sub DoSomething()
60+
Dim value As Long
61+
Dim bar As Long
62+
value = 42
63+
bar = 23
64+
Debug.Print 42
65+
End Sub";
66+
67+
var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new VariableNotUsedInspection(state));
68+
Assert.AreEqual(expectedCode, actualCode);
69+
}
70+
71+
[Test]
72+
[Category("QuickFixes")]
73+
public void IgnoreModuleMultiple_AddsOneAnnotation_NoIgnoreModuleYet()
74+
{
75+
var inputCode =
76+
@"
77+
Public Sub DoSomething()
78+
Dim value As Long
79+
Dim bar As Long
80+
value = 42
81+
bar = 23
82+
Debug.Print 42
83+
End Sub";
84+
85+
var expectedCode =
86+
@"'@IgnoreModule VariableNotUsed
87+
88+
Public Sub DoSomething()
89+
Dim value As Long
90+
Dim bar As Long
91+
value = 42
92+
bar = 23
93+
Debug.Print 42
94+
End Sub";
95+
96+
var actualCode = ApplyQuickFixToAllInspectionResults(inputCode, state => new VariableNotUsedInspection(state));
97+
Assert.AreEqual(expectedCode, actualCode);
98+
}
99+
100+
[Test]
101+
[Category("QuickFixes")]
102+
public void IgnoreModuleMultiple_AddsOneAnnotation_IgnoreModuleAlreadyThere()
103+
{
104+
var inputCode =
105+
@"'@IgnoreModule AssignmentNotUsed
106+
Public Sub DoSomething()
107+
Dim value As Long
108+
Dim bar As Long
109+
value = 42
110+
bar = 23
111+
Debug.Print 42
112+
End Sub";
113+
114+
var expectedCode =
115+
@"'@IgnoreModule VariableNotUsed, AssignmentNotUsed
116+
Public Sub DoSomething()
117+
Dim value As Long
118+
Dim bar As Long
119+
value = 42
120+
bar = 23
121+
Debug.Print 42
122+
End Sub";
123+
124+
var actualCode = ApplyQuickFixToAllInspectionResults(inputCode, state => new VariableNotUsedInspection(state));
125+
Assert.AreEqual(expectedCode, actualCode);
126+
}
127+
128+
protected override IQuickFix QuickFix(RubberduckParserState state)
129+
{
130+
var annotationUpdater = new AnnotationUpdater();
131+
var inspections = new List<IInspection> {new VariableNotUsedInspection(state)};
132+
return new IgnoreInModuleQuickFix(annotationUpdater, state, inspections);
133+
}
134+
}
135+
}

0 commit comments

Comments
 (0)