Skip to content

Commit a6d6d18

Browse files
authored
Merge pull request #4593 from MDoerner/FixIgnoreOnce
Rewrite ignore once quickfix
2 parents 87f612b + 1fb36ef commit a6d6d18

File tree

4 files changed

+195
-86
lines changed

4 files changed

+195
-86
lines changed

Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs

Lines changed: 84 additions & 71 deletions
Original file line numberDiff line numberDiff line change
@@ -1,15 +1,17 @@
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;
1111
using Rubberduck.Parsing.Rewriter;
12+
using Rubberduck.Parsing.Symbols;
1213
using Rubberduck.Parsing.VBA;
14+
using Rubberduck.Parsing.VBA.Parsing;
1315

1416
namespace Rubberduck.Inspections.QuickFixes
1517
{
@@ -29,98 +31,109 @@ public IgnoreOnceQuickFix(RubberduckParserState state, IEnumerable<IInspection>
2931

3032
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
3133
{
32-
var annotationText = $"'@Ignore {result.Inspection.AnnotationName}";
33-
34-
int annotationLine;
35-
//TODO: Make this use the parse tree instead of the code module.
36-
var component = _state.ProjectsProvider.Component(result.QualifiedSelection.QualifiedName);
37-
using (var module = component.CodeModule)
34+
if (result.Target?.DeclarationType.HasFlag(DeclarationType.Module) ?? false)
3835
{
39-
annotationLine = result.QualifiedSelection.Selection.StartLine;
40-
while (annotationLine != 1 && module.GetLines(annotationLine - 1, 1).EndsWith(" _"))
41-
{
42-
annotationLine--;
43-
}
36+
FixModule(result, rewriteSession);
4437
}
45-
46-
RuleContext treeRoot = result.Context;
47-
while (treeRoot.Parent != null)
38+
else
4839
{
49-
treeRoot = treeRoot.Parent;
40+
FixNonModule(result, rewriteSession);
5041
}
42+
}
5143

52-
var listener = new CommentOrAnnotationListener();
53-
ParseTreeWalker.Default.Walk(listener, treeRoot);
54-
var commentContext = listener.Contexts.LastOrDefault(i => i.Stop.TokenIndex <= result.Context.Start.TokenIndex);
55-
var commented = commentContext?.Stop.Line + 1 == annotationLine;
44+
private void FixNonModule(IInspectionResult result, IRewriteSession rewriteSession)
45+
{
46+
int insertionIndex;
47+
string insertText;
48+
var annotationText = $"'@Ignore {result.Inspection.AnnotationName}";
5649

57-
var rewriter = rewriteSession.CheckOutModuleRewriter(result.QualifiedSelection.QualifiedName);
50+
var module = result.QualifiedSelection.QualifiedName;
51+
var parseTree = _state.GetParseTree(module, CodeKind.CodePaneCode);
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);
5857

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

99-
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.IgnoreOnce;
95+
private static 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+
}
100103

101-
private class CommentOrAnnotationListener : VBAParserBaseListener
104+
private void FixModule(IInspectionResult result, IRewriteSession rewriteSession)
102105
{
103-
private readonly IList<VBAParser.CommentOrAnnotationContext> _contexts = new List<VBAParser.CommentOrAnnotationContext>();
104-
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();
105112

106-
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)
107119
{
108-
_contexts.Add(context);
120+
insertionIndex = 0;
121+
insertText = $"'@IgnoreModule {result.Inspection.AnnotationName}{Environment.NewLine}";
122+
rewriter.InsertBefore(insertionIndex, insertText);
123+
return;
109124
}
125+
126+
insertionIndex = firstIgnoreModuleAnnotation.Context.annotationName().Stop.TokenIndex;
127+
insertText = $" {result.Inspection.AnnotationName},";
128+
rewriter.InsertAfter(insertionIndex, insertText);
110129
}
111130

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

125138
public override void ExitEndOfLine([NotNull] VBAParser.EndOfLineContext context)
126139
{

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

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -649,6 +649,16 @@ public void SetModuleComments(QualifiedModuleName module, IEnumerable<CommentNod
649649
_moduleStates[module].SetComments(new List<CommentNode>(comments));
650650
}
651651

652+
public IReadOnlyCollection<CommentNode> GetModuleComments(QualifiedModuleName module)
653+
{
654+
if (!_moduleStates.TryGetValue(module, out var moduleState))
655+
{
656+
return new List<CommentNode>();
657+
}
658+
659+
return moduleState.Comments;
660+
}
661+
652662
public List<IAnnotation> AllAnnotations
653663
{
654664
get

0 commit comments

Comments
 (0)