Skip to content

Commit 77d09fb

Browse files
committed
Make IgnoreOnceQuickFix use the AnnotationUpdater
1 parent ffe250a commit 77d09fb

File tree

3 files changed

+40
-85
lines changed

3 files changed

+40
-85
lines changed

Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs

Lines changed: 29 additions & 81 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using Antlr4.Runtime.Misc;
55
using Antlr4.Runtime.Tree;
66
using Rubberduck.Inspections.Abstract;
7+
using Rubberduck.Parsing;
78
using Rubberduck.Parsing.Annotations;
89
using Rubberduck.Parsing.Grammar;
910
using Rubberduck.Parsing.Inspections;
@@ -18,11 +19,13 @@ namespace Rubberduck.Inspections.QuickFixes
1819
public sealed class IgnoreOnceQuickFix : QuickFixBase
1920
{
2021
private readonly RubberduckParserState _state;
22+
private readonly IAnnotationUpdater _annotationUpdater;
2123

22-
public IgnoreOnceQuickFix(RubberduckParserState state, IEnumerable<IInspection> inspections)
24+
public IgnoreOnceQuickFix(IAnnotationUpdater annotationUpdater, RubberduckParserState state, IEnumerable<IInspection> inspections)
2325
: base(inspections.Select(s => s.GetType()).Where(i => i.CustomAttributes.All(a => a.AttributeType != typeof(CannotAnnotateAttribute))).ToArray())
2426
{
2527
_state = state;
28+
_annotationUpdater = annotationUpdater;
2629
}
2730

2831
public override bool CanFixInProcedure => false;
@@ -43,102 +46,47 @@ public override void Fix(IInspectionResult result, IRewriteSession rewriteSessio
4346

4447
private void FixNonModule(IInspectionResult result, IRewriteSession rewriteSession)
4548
{
46-
int insertionIndex;
47-
string insertText;
48-
var annotationText = $"'@Ignore {result.Inspection.AnnotationName}";
49-
5049
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);
57-
58-
var rewriter = rewriteSession.CheckOutModuleRewriter(module);
59-
60-
if (previousEol == null)
61-
{
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;
67-
}
50+
var lineToAnnotate = result.QualifiedSelection.Selection.StartLine;
51+
var existingIgnoreAnnotation = _state.DeclarationFinder.FindAnnotations(module, lineToAnnotate)
52+
.OfType<IgnoreAnnotation>()
53+
.FirstOrDefault();
6854

69-
var commentContext = previousEol.commentOrAnnotation();
70-
if (commentContext == null)
55+
var annotationType = AnnotationType.Ignore;
56+
if (existingIgnoreAnnotation != null)
7157
{
72-
insertionIndex = previousEol.Start.TokenIndex;
73-
var indent = WhitespaceAfter(previousEol);
74-
insertText = $"{Environment.NewLine}{indent}{annotationText}";
75-
rewriter.InsertBefore(insertionIndex, insertText);
76-
return;
58+
var annotationValues = existingIgnoreAnnotation.InspectionNames.ToList();
59+
annotationValues.Insert(0, result.Inspection.AnnotationName);
60+
_annotationUpdater.UpdateAnnotation(rewriteSession, existingIgnoreAnnotation, annotationType, annotationValues);
7761
}
78-
79-
var ignoreAnnotation = commentContext.annotationList()?.annotation()
80-
.FirstOrDefault(annotationContext => annotationContext.annotationName().GetText() == AnnotationType.Ignore.ToString());
81-
if (ignoreAnnotation == null)
62+
else
8263
{
83-
insertionIndex = commentContext.Stop.TokenIndex;
84-
var indent = WhitespaceAfter(previousEol);
85-
insertText = $"{indent}{annotationText}{Environment.NewLine}";
86-
rewriter.InsertAfter(insertionIndex, insertText);
87-
return;
64+
var annotationValues = new List<string> { result.Inspection.AnnotationName };
65+
_annotationUpdater.AddAnnotation(rewriteSession, new QualifiedContext(module, result.Context), annotationType, annotationValues);
8866
}
89-
90-
insertionIndex = ignoreAnnotation.annotationName().Stop.TokenIndex;
91-
insertText = $" {result.Inspection.AnnotationName},";
92-
rewriter.InsertAfter(insertionIndex, insertText);
93-
}
94-
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;
10267
}
10368

10469
private void FixModule(IInspectionResult result, IRewriteSession rewriteSession)
10570
{
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)
71+
var moduleDeclaration = result.Target;
72+
var existingIgnoreModuleAnnotation = moduleDeclaration.Annotations
73+
.OfType<IgnoreModuleAnnotation>()
11174
.FirstOrDefault();
11275

113-
var rewriter = rewriteSession.CheckOutModuleRewriter(module);
114-
115-
int insertionIndex;
116-
string insertText;
117-
118-
if (firstIgnoreModuleAnnotation == null)
76+
var annotationType = AnnotationType.IgnoreModule;
77+
if (existingIgnoreModuleAnnotation != null)
11978
{
120-
insertionIndex = 0;
121-
insertText = $"'@IgnoreModule {result.Inspection.AnnotationName}{Environment.NewLine}";
122-
rewriter.InsertBefore(insertionIndex, insertText);
123-
return;
79+
var annotationValues = existingIgnoreModuleAnnotation.InspectionNames.ToList();
80+
annotationValues.Insert(0, result.Inspection.AnnotationName);
81+
_annotationUpdater.UpdateAnnotation(rewriteSession, existingIgnoreModuleAnnotation, annotationType, annotationValues);
12482
}
125-
126-
insertionIndex = firstIgnoreModuleAnnotation.Context.annotationName().Stop.TokenIndex;
127-
insertText = $" {result.Inspection.AnnotationName},";
128-
rewriter.InsertAfter(insertionIndex, insertText);
129-
}
130-
131-
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.IgnoreOnce;
132-
133-
private class EndOfLineListener : VBAParserBaseListener
134-
{
135-
private readonly IList<VBAParser.EndOfLineContext> _contexts = new List<VBAParser.EndOfLineContext>();
136-
public IEnumerable<VBAParser.EndOfLineContext> Contexts => _contexts;
137-
138-
public override void ExitEndOfLine([NotNull] VBAParser.EndOfLineContext context)
83+
else
13984
{
140-
_contexts.Add(context);
85+
var annotationValues = new List<string> { result.Inspection.AnnotationName };
86+
_annotationUpdater.AddAnnotation(rewriteSession, moduleDeclaration, annotationType, annotationValues);
14187
}
14288
}
89+
90+
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.IgnoreOnce;
14391
}
14492
}

Rubberduck.Parsing/VBA/AnnotationUpdater.cs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,12 @@ public void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext conte
4040
}
4141

4242
var previousEndOfLine = PreviousEndOfLine(context.Context);
43+
if (previousEndOfLine == null)
44+
{
45+
//We are on the first logical line, but not the first physical line.
46+
return;
47+
}
48+
4349
if (context.Context.start.Line > previousEndOfLine.stop.Line + 1)
4450
{
4551
_logger.Warn("Tried to add an annotation to a context not on the first physical line of a logical line.");

RubberduckTests/QuickFixes/IgnoreOnceQuickFixTests.cs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -321,6 +321,7 @@ Public Sub Foo()
321321

322322
[Test]
323323
[Category("QuickFixes")]
324+
[Ignore("With the current annotation scoping rules, this test makes no sense since the Ignore annotation will not attach to the offending context.")]
324325
public void MultilineParameter_IgnoreQuickFixWorks()
325326
{
326327
const string inputCode =
@@ -732,7 +733,7 @@ Dim str As String
732733
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
733734
var rewriteSession = rewritingManager.CheckOutCodePaneSession();
734735

735-
new IgnoreOnceQuickFix(state, new[] { inspection }).Fix(inspectionResults.First(), rewriteSession);
736+
new IgnoreOnceQuickFix(new AnnotationUpdater(), state, new[] { inspection }).Fix(inspectionResults.First(), rewriteSession);
736737
var actualCode = rewriteSession.CheckOutModuleRewriter(component.QualifiedModuleName).GetText();
737738

738739
Assert.AreEqual(expectedCode, actualCode);
@@ -766,7 +767,7 @@ Sub Ffffff()
766767
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
767768
var rewriteSession = rewritingManager.CheckOutCodePaneSession();
768769

769-
new IgnoreOnceQuickFix(state, new[] { inspection }).Fix(inspectionResults.First(), rewriteSession);
770+
new IgnoreOnceQuickFix(new AnnotationUpdater(), state, new[] { inspection }).Fix(inspectionResults.First(), rewriteSession);
770771
var actualCode = rewriteSession.CheckOutModuleRewriter(component.QualifiedModuleName).GetText();
771772

772773
Assert.AreEqual(expectedCode, actualCode);
@@ -1063,7 +1064,7 @@ private string ApplyIgnoreOnceToFirstResult(
10631064
var resultToFix = inspectionResults.First();
10641065
var rewriteSession = rewritingManager.CheckOutCodePaneSession();
10651066

1066-
var quickFix = new IgnoreOnceQuickFix(state, new[] {inspection});
1067+
var quickFix = new IgnoreOnceQuickFix(new AnnotationUpdater(), state, new[] {inspection});
10671068
quickFix.Fix(resultToFix, rewriteSession);
10681069

10691070
return rewriteSession.CheckOutModuleRewriter(moduleName).GetText();
@@ -1139,7 +1140,7 @@ private string ApplyIgnoreOnceToAllResults(
11391140
var inspectionResults = InspectionResults(inspection, state);
11401141
var rewriteSession = rewritingManager.CheckOutCodePaneSession();
11411142

1142-
var quickFix = new IgnoreOnceQuickFix(state, new[] { inspection });
1143+
var quickFix = new IgnoreOnceQuickFix(new AnnotationUpdater(), state, new[] { inspection });
11431144

11441145
foreach (var resultToFix in inspectionResults)
11451146
{

0 commit comments

Comments
 (0)