Skip to content

Commit d7c8bbf

Browse files
committed
Make IgnoreOnceQuickfix able to handle modules
Previously, the fix silently expected to be handed an inspection result with a parser context. Module inspection results have none. Moreover it always used Ignore whereas modules require IgnoreModule.
1 parent 87f612b commit d7c8bbf

File tree

3 files changed

+54
-11
lines changed

3 files changed

+54
-11
lines changed

Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs

Lines changed: 12 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,9 @@
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,32 +31,31 @@ public IgnoreOnceQuickFix(RubberduckParserState state, IEnumerable<IInspection>
2931

3032
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
3133
{
32-
var annotationText = $"'@Ignore {result.Inspection.AnnotationName}";
34+
var annotationText = result.Target?.DeclarationType.HasFlag(DeclarationType.Module) == true
35+
? $"'@IgnoreModule {result.Inspection.AnnotationName}"
36+
: $"'@Ignore {result.Inspection.AnnotationName}";
3337

3438
int annotationLine;
3539
//TODO: Make this use the parse tree instead of the code module.
3640
var component = _state.ProjectsProvider.Component(result.QualifiedSelection.QualifiedName);
37-
using (var module = component.CodeModule)
41+
using (var codeModule = component.CodeModule)
3842
{
3943
annotationLine = result.QualifiedSelection.Selection.StartLine;
40-
while (annotationLine != 1 && module.GetLines(annotationLine - 1, 1).EndsWith(" _"))
44+
while (annotationLine != 1 && codeModule.GetLines(annotationLine - 1, 1).EndsWith(" _"))
4145
{
4246
annotationLine--;
4347
}
4448
}
4549

46-
RuleContext treeRoot = result.Context;
47-
while (treeRoot.Parent != null)
48-
{
49-
treeRoot = treeRoot.Parent;
50-
}
50+
var module = result.QualifiedSelection.QualifiedName;
51+
var parseTree = _state.GetParseTree(module, CodeKind.CodePaneCode);
5152

5253
var listener = new CommentOrAnnotationListener();
53-
ParseTreeWalker.Default.Walk(listener, treeRoot);
54+
ParseTreeWalker.Default.Walk(listener, parseTree);
5455
var commentContext = listener.Contexts.LastOrDefault(i => i.Stop.TokenIndex <= result.Context.Start.TokenIndex);
5556
var commented = commentContext?.Stop.Line + 1 == annotationLine;
5657

57-
var rewriter = rewriteSession.CheckOutModuleRewriter(result.QualifiedSelection.QualifiedName);
58+
var rewriter = rewriteSession.CheckOutModuleRewriter(module);
5859

5960
if (commented)
6061
{
@@ -82,7 +83,7 @@ public override void Fix(IInspectionResult result, IRewriteSession rewriteSessio
8283
else
8384
{
8485
var eol = new EndOfLineListener();
85-
ParseTreeWalker.Default.Walk(eol, treeRoot);
86+
ParseTreeWalker.Default.Walk(eol, parseTree);
8687

8788
// we subtract 2 here to get the insertion index to A) account for VBE's one-based indexing
8889
// and B) to get the newline token that introduces that line

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

RubberduckTests/QuickFixes/IgnoreOnceQuickFixTests.cs

Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -830,6 +830,38 @@ Sub Foo(arg1)
830830
Assert.AreEqual(expectedCode, actualCode);
831831
}
832832

833+
834+
[Test]
835+
[Category("QuickFixes")]
836+
public void EmptyModule_IgnoreQuickFixWorks()
837+
{
838+
const string inputCode =
839+
@"Option Explicit";
840+
841+
const string expectedCode =
842+
@"'@IgnoreModule EmptyModule
843+
Option Explicit";
844+
845+
var actualCode = ApplyIgnoreOnceToFirstResult(inputCode, state => new EmptyModuleInspection(state), TestStandardModuleVbeSetup);
846+
Assert.AreEqual(expectedCode, actualCode);
847+
}
848+
849+
850+
[Test]
851+
[Category("QuickFixes")]
852+
public void ModuleWithoutFolder_IgnoreQuickFixWorks()
853+
{
854+
const string inputCode =
855+
@"Option Explicit";
856+
857+
const string expectedCode =
858+
@"'@IgnoreModule ModuleWithoutFolder
859+
Option Explicit";
860+
861+
var actualCode = ApplyIgnoreOnceToFirstResult(inputCode, state => new ModuleWithoutFolderInspection(state), TestStandardModuleVbeSetup);
862+
Assert.AreEqual(expectedCode, actualCode);
863+
}
864+
833865
[Test]
834866
[Category("QuickFixes")]
835867
public void WriteOnlyProperty_IgnoreQuickFixWorks()

0 commit comments

Comments
 (0)