Skip to content

Commit b011dff

Browse files
committed
Rewrite the IgnoreOnceQuickfix
This removes some bugs around module inspection results, removes the use of the code modules and makes the quickfix honor indentation. Moreover, it now recognizes an existing Ignore annotation that it not the first one in an annotation list.
1 parent d7c8bbf commit b011dff

File tree

3 files changed

+150
-84
lines changed

3 files changed

+150
-84
lines changed

Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs

Lines changed: 81 additions & 69 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,10 @@
11
using System;
22
using System.Collections.Generic;
33
using System.Linq;
4-
using Antlr4.Runtime;
54
using Antlr4.Runtime.Misc;
65
using Antlr4.Runtime.Tree;
76
using Rubberduck.Inspections.Abstract;
7+
using Rubberduck.Parsing.Annotations;
88
using Rubberduck.Parsing.Grammar;
99
using Rubberduck.Parsing.Inspections;
1010
using Rubberduck.Parsing.Inspections.Abstract;
@@ -31,97 +31,109 @@ public IgnoreOnceQuickFix(RubberduckParserState state, IEnumerable<IInspection>
3131

3232
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
3333
{
34-
var annotationText = result.Target?.DeclarationType.HasFlag(DeclarationType.Module) == true
35-
? $"'@IgnoreModule {result.Inspection.AnnotationName}"
36-
: $"'@Ignore {result.Inspection.AnnotationName}";
37-
38-
int annotationLine;
39-
//TODO: Make this use the parse tree instead of the code module.
40-
var component = _state.ProjectsProvider.Component(result.QualifiedSelection.QualifiedName);
41-
using (var codeModule = component.CodeModule)
34+
if (result.Target?.DeclarationType.HasFlag(DeclarationType.Module) == true)
4235
{
43-
annotationLine = result.QualifiedSelection.Selection.StartLine;
44-
while (annotationLine != 1 && codeModule.GetLines(annotationLine - 1, 1).EndsWith(" _"))
45-
{
46-
annotationLine--;
47-
}
36+
FixModule(result, rewriteSession);
4837
}
38+
else
39+
{
40+
FixNonModule(result, rewriteSession);
41+
}
42+
}
43+
44+
private void FixNonModule(IInspectionResult result, IRewriteSession rewriteSession)
45+
{
46+
int insertionIndex;
47+
string insertText;
48+
var annotationText = $"'@Ignore {result.Inspection.AnnotationName}";
4949

5050
var module = result.QualifiedSelection.QualifiedName;
5151
var parseTree = _state.GetParseTree(module, CodeKind.CodePaneCode);
52-
53-
var listener = new CommentOrAnnotationListener();
54-
ParseTreeWalker.Default.Walk(listener, parseTree);
55-
var commentContext = listener.Contexts.LastOrDefault(i => i.Stop.TokenIndex <= result.Context.Start.TokenIndex);
56-
var commented = commentContext?.Stop.Line + 1 == annotationLine;
52+
var eolListener = new EndOfLineListener();
53+
ParseTreeWalker.Default.Walk(eolListener, parseTree);
54+
var previousEol = eolListener.Contexts
55+
.OrderBy(eol => eol.Start.TokenIndex)
56+
.LastOrDefault(eol => eol.Start.Line < result.QualifiedSelection.Selection.StartLine);
5757

5858
var rewriter = rewriteSession.CheckOutModuleRewriter(module);
5959

60-
if (commented)
60+
if (previousEol == null)
6161
{
62-
var annotation = commentContext.annotationList()?.annotation(0);
63-
if (annotation != null && annotation.GetText().StartsWith("Ignore"))
64-
{
65-
rewriter.InsertAfter(annotation.annotationName().Stop.TokenIndex, $" {result.Inspection.AnnotationName},");
66-
}
67-
else
68-
{
69-
var indent = new string(Enumerable.Repeat(' ', commentContext.Start.Column).ToArray());
70-
rewriter.InsertAfter(commentContext.Stop.TokenIndex, $"{indent}{annotationText}{Environment.NewLine}");
71-
}
62+
// The context to get annotated is on the first line; we need to insert before token index 0.
63+
insertionIndex = 0;
64+
insertText = annotationText + Environment.NewLine;
65+
rewriter.InsertBefore(insertionIndex, insertText);
66+
return;
7267
}
73-
else
68+
69+
var commentContext = previousEol.commentOrAnnotation();
70+
if (commentContext == null)
7471
{
75-
int insertIndex;
76-
77-
// this value is used when the annotation should be on line 1--we need to insert before token index 0
78-
if (annotationLine == 1)
79-
{
80-
insertIndex = 0;
81-
annotationText += Environment.NewLine;
82-
}
83-
else
84-
{
85-
var eol = new EndOfLineListener();
86-
ParseTreeWalker.Default.Walk(eol, parseTree);
87-
88-
// we subtract 2 here to get the insertion index to A) account for VBE's one-based indexing
89-
// and B) to get the newline token that introduces that line
90-
var eolContext = eol.Contexts.OrderBy(o => o.Start.TokenIndex).ElementAt(annotationLine - 2);
91-
insertIndex = eolContext.Start.TokenIndex;
92-
93-
annotationText = Environment.NewLine + annotationText;
94-
}
95-
96-
rewriter.InsertBefore(insertIndex, annotationText);
72+
insertionIndex = previousEol.Start.TokenIndex;
73+
var indent = WhitespaceAfter(previousEol);
74+
insertText = $"{Environment.NewLine}{indent}{annotationText}";
75+
rewriter.InsertBefore(insertionIndex, insertText);
76+
return;
9777
}
78+
79+
var ignoreAnnotation = commentContext.annotationList()?.annotation()
80+
.FirstOrDefault(annotationContext => annotationContext.annotationName().GetText() == AnnotationType.Ignore.ToString());
81+
if (ignoreAnnotation == null)
82+
{
83+
insertionIndex = commentContext.Stop.TokenIndex;
84+
var indent = WhitespaceAfter(previousEol);
85+
insertText = $"{indent}{annotationText}{Environment.NewLine}";
86+
rewriter.InsertAfter(insertionIndex, insertText);
87+
return;
88+
}
89+
90+
insertionIndex = ignoreAnnotation.annotationName().Stop.TokenIndex;
91+
insertText = $" {result.Inspection.AnnotationName},";
92+
rewriter.InsertAfter(insertionIndex, insertText);
9893
}
9994

100-
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.IgnoreOnce;
95+
private string WhitespaceAfter(VBAParser.EndOfLineContext endOfLine)
96+
{
97+
var individualEndOfStatement = (VBAParser.IndividualNonEOFEndOfStatementContext) endOfLine.Parent;
98+
var whiteSpaceOnNextLine = individualEndOfStatement.whiteSpace(0);
99+
return whiteSpaceOnNextLine != null
100+
? whiteSpaceOnNextLine.GetText()
101+
: string.Empty;
102+
}
101103

102-
private class CommentOrAnnotationListener : VBAParserBaseListener
104+
private void FixModule(IInspectionResult result, IRewriteSession rewriteSession)
103105
{
104-
private readonly IList<VBAParser.CommentOrAnnotationContext> _contexts = new List<VBAParser.CommentOrAnnotationContext>();
105-
public IEnumerable<VBAParser.CommentOrAnnotationContext> Contexts => _contexts;
106+
var module = result.QualifiedSelection.QualifiedName;
107+
var moduleAnnotations = _state.GetModuleAnnotations(module);
108+
var firstIgnoreModuleAnnotation = moduleAnnotations
109+
.Where(annotation => annotation.AnnotationType == AnnotationType.IgnoreModule)
110+
.OrderBy(annotation => annotation.Context.Start.TokenIndex)
111+
.FirstOrDefault();
106112

107-
public override void ExitCommentOrAnnotation([NotNull] VBAParser.CommentOrAnnotationContext context)
113+
var rewriter = rewriteSession.CheckOutModuleRewriter(module);
114+
115+
int insertionIndex;
116+
string insertText;
117+
118+
if (firstIgnoreModuleAnnotation == null)
108119
{
109-
_contexts.Add(context);
120+
insertionIndex = 0;
121+
insertText = $"'@IgnoreModule {result.Inspection.AnnotationName}{Environment.NewLine}";
122+
rewriter.InsertBefore(insertionIndex, insertText);
123+
return;
110124
}
125+
126+
insertionIndex = firstIgnoreModuleAnnotation.Context.annotationName().Stop.TokenIndex;
127+
insertText = $" {result.Inspection.AnnotationName},";
128+
rewriter.InsertAfter(insertionIndex, insertText);
111129
}
112130

131+
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.IgnoreOnce;
132+
113133
private class EndOfLineListener : VBAParserBaseListener
114134
{
115-
private readonly IList<ParserRuleContext> _contexts = new List<ParserRuleContext>();
116-
public IEnumerable<ParserRuleContext> Contexts => _contexts;
117-
118-
public override void ExitWhiteSpace([NotNull] VBAParser.WhiteSpaceContext context)
119-
{
120-
if (context.GetText().Contains(Environment.NewLine))
121-
{
122-
_contexts.Add(context);
123-
}
124-
}
135+
private readonly IList<VBAParser.EndOfLineContext> _contexts = new List<VBAParser.EndOfLineContext>();
136+
public IEnumerable<VBAParser.EndOfLineContext> Contexts => _contexts;
125137

126138
public override void ExitEndOfLine([NotNull] VBAParser.EndOfLineContext context)
127139
{

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -898,7 +898,7 @@ statementKeyword :
898898
;
899899

900900
endOfLine :
901-
whiteSpace? NEWLINE whiteSpace?
901+
whiteSpace? NEWLINE
902902
| whiteSpace? commentOrAnnotation
903903
;
904904

RubberduckTests/QuickFixes/IgnoreOnceQuickFixTests.cs

Lines changed: 68 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ Dim foo As Double
3131
const string expectedCode =
3232
@"Sub ExcelSub()
3333
Dim foo As Double
34-
'@Ignore ApplicationWorksheetFunction
34+
'@Ignore ApplicationWorksheetFunction
3535
foo = Application.Pi
3636
End Sub";
3737

@@ -69,7 +69,7 @@ public void ConstantNotUsed_IgnoreQuickFixWorks()
6969

7070
const string expectedCode =
7171
@"Public Sub Foo()
72-
'@Ignore ConstantNotUsed
72+
'@Ignore ConstantNotUsed
7373
Const const1 As Integer = 9
7474
End Sub";
7575

@@ -88,7 +88,7 @@ public void EmptyStringLiteral_IgnoreQuickFixWorks()
8888

8989
const string expectedCode =
9090
@"Public Sub Foo(ByRef arg1 As String)
91-
'@Ignore EmptyStringLiteral
91+
'@Ignore EmptyStringLiteral
9292
arg1 = """"
9393
End Sub";
9494

@@ -174,7 +174,7 @@ Dim arr1() As Variant
174174
const string expectedCode =
175175
@"Sub foo()
176176
Dim arr1() As Variant
177-
'@Ignore ImplicitActiveSheetReference
177+
'@Ignore ImplicitActiveSheetReference
178178
arr1 = Range(""A1:B2"")
179179
End Sub";
180180

@@ -197,7 +197,7 @@ Dim sheet As Worksheet
197197
@"
198198
Sub foo()
199199
Dim sheet As Worksheet
200-
'@Ignore ImplicitActiveWorkbookReference
200+
'@Ignore ImplicitActiveWorkbookReference
201201
Set sheet = Worksheets(""Sheet1"")
202202
End Sub";
203203

@@ -356,7 +356,7 @@ public void MultipleDeclarations_IgnoreQuickFixWorks()
356356

357357
const string expectedCode =
358358
@"Public Sub Foo()
359-
'@Ignore MultipleDeclarations
359+
'@Ignore MultipleDeclarations
360360
Dim var1 As Integer, var2 As String
361361
End Sub";
362362

@@ -401,7 +401,7 @@ Dim target As Object
401401
Private Sub DoSomething()
402402
403403
Dim target As Object
404-
'@Ignore ObjectVariableNotSet
404+
'@Ignore ObjectVariableNotSet
405405
target = New Object
406406
407407
target.Value = ""forgot something?""
@@ -428,12 +428,12 @@ Call Foo
428428

429429
const string expectedCode =
430430
@"Sub Foo()
431-
'@Ignore ObsoleteCallStatement
431+
'@Ignore ObsoleteCallStatement
432432
Call Goo(1, ""test"")
433433
End Sub
434434
435435
Sub Goo(arg1 As Integer, arg1 As String)
436-
'@Ignore ObsoleteCallStatement
436+
'@Ignore ObsoleteCallStatement
437437
Call Foo
438438
End Sub";
439439

@@ -467,7 +467,7 @@ Error 91
467467

468468
const string expectedCode =
469469
@"Sub Foo()
470-
'@Ignore ObsoleteErrorSyntax
470+
'@Ignore ObsoleteErrorSyntax
471471
Error 91
472472
End Sub";
473473

@@ -508,7 +508,7 @@ Dim var2 As Integer
508508
Dim var1 As Integer
509509
Dim var2 As Integer
510510
511-
'@Ignore ObsoleteLetStatement
511+
'@Ignore ObsoleteLetStatement
512512
Let var2 = var1
513513
End Sub";
514514

@@ -657,7 +657,7 @@ Dim b As New Collection
657657

658658
const string expectedCode =
659659
@"Sub Foo()
660-
'@Ignore SelfAssignedDeclaration
660+
'@Ignore SelfAssignedDeclaration
661661
Dim b As New Collection
662662
End Sub";
663663

@@ -681,7 +681,7 @@ Dim bb As Boolean
681681
@"Sub Foo()
682682
Dim b As Boolean
683683
Dim bb As Boolean
684-
'@Ignore UnassignedVariableUsage
684+
'@Ignore UnassignedVariableUsage
685685
bb = b
686686
End Sub";
687687

@@ -896,7 +896,7 @@ If True Then
896896
const string expectedCode =
897897
@"Sub Foo()
898898
Dim d As Boolean
899-
'@Ignore BooleanAssignedInIfElse
899+
'@Ignore BooleanAssignedInIfElse
900900
If True Then
901901
d = True
902902
Else
@@ -928,6 +928,60 @@ public void IgnoreQuickFixAppendsToExistingAnnotation()
928928
Assert.AreEqual(expectedCode, actualCode);
929929
}
930930

931+
[Test]
932+
[Category("QuickFixes")]
933+
public void IgnoreQuickFixPrependsToExistingAnnotation_Module()
934+
{
935+
const string inputCode =
936+
@"'@IgnoreModule EmptyModule
937+
Option Explicit";
938+
939+
const string expectedCode =
940+
@"'@IgnoreModule ModuleWithoutFolder, EmptyModule
941+
Option Explicit";
942+
943+
var actualCode = ApplyIgnoreOnceToFirstResult(inputCode, state => new ModuleWithoutFolderInspection(state), TestStandardModuleVbeSetup);
944+
Assert.AreEqual(expectedCode, actualCode);
945+
}
946+
947+
[Test]
948+
[Category("QuickFixes")]
949+
public void IgnoreQuickFixDoesNotAppendToExistingAnnotationMixed_ModuleAfterNonModule()
950+
{
951+
const string inputCode =
952+
@"'@Ignore ParameterCanBeByVal
953+
Private Sub Foo(arg)
954+
End Sub";
955+
956+
const string expectedCode =
957+
@"'@IgnoreModule ModuleWithoutFolder
958+
'@Ignore ParameterCanBeByVal
959+
Private Sub Foo(arg)
960+
End Sub";
961+
962+
var actualCode = ApplyIgnoreOnceToFirstResult(inputCode, state => new ModuleWithoutFolderInspection(state), TestStandardModuleVbeSetup);
963+
Assert.AreEqual(expectedCode, actualCode);
964+
}
965+
966+
[Test]
967+
[Category("QuickFixes")]
968+
public void IgnoreQuickFixDoesNotPrependToExistingAnnotationMixed_NonModuleAfterModule()
969+
{
970+
const string inputCode =
971+
@"'@IgnoreModule ModuleWithoutFolder
972+
Private Sub Foo(arg)
973+
End Sub";
974+
975+
const string expectedCode =
976+
@"'@IgnoreModule ModuleWithoutFolder
977+
'@Ignore ParameterCanBeByVal
978+
Private Sub Foo(arg)
979+
End Sub";
980+
981+
var actualCode = ApplyIgnoreOnceToFirstResult(inputCode, state => new ParameterCanBeByValInspection(state), TestStandardModuleVbeSetup);
982+
Assert.AreEqual(expectedCode, actualCode);
983+
}
984+
931985
[Test]
932986
[Category("QuickFixes")]
933987
public void IgnoreQuickFixAddsAnnotationAfterComment()

0 commit comments

Comments
 (0)