Skip to content

Commit 8a1d8bd

Browse files
authored
Merge pull request #4679 from MDoerner/AnnotationQuickFixesForAttributeInspections
Annotation quick fixes for attribute inspections
2 parents 1d11646 + 6826974 commit 8a1d8bd

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

43 files changed

+2269
-301
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -77,10 +77,7 @@ private static bool MissesCorrespondingMemberAnnotation(Declaration declaration,
7777

7878
private static string AttributeBaseName(Declaration declaration, AttributeNode attribute)
7979
{
80-
var attributeName = attribute.Name;
81-
return attributeName.StartsWith($"{declaration.IdentifierName}.")
82-
? attributeName.Substring(declaration.IdentifierName.Length + 1)
83-
: attributeName;
80+
return Attributes.AttributeBaseName(attribute.Name, declaration.IdentifierName);
8481
}
8582
}
8683
}

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs

Lines changed: 1 addition & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -61,27 +61,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
6161

6262
private static bool IsDefaultAttribute(Declaration declaration, AttributeNode attribute)
6363
{
64-
switch (attribute.Name)
65-
{
66-
case "VB_Name":
67-
return true;
68-
case "VB_GlobalNameSpace":
69-
return declaration.DeclarationType.HasFlag(DeclarationType.ClassModule)
70-
&& attribute.Values[0].Equals(Tokens.False);
71-
case "VB_Exposed":
72-
return declaration.DeclarationType.HasFlag(DeclarationType.ClassModule)
73-
&& attribute.Values[0].Equals(Tokens.False);
74-
case "VB_Creatable":
75-
return declaration.DeclarationType.HasFlag(DeclarationType.ClassModule)
76-
&& attribute.Values[0].Equals(Tokens.False);
77-
case "VB_PredeclaredId":
78-
return (declaration.QualifiedModuleName.ComponentType == ComponentType.ClassModule
79-
&& attribute.Values[0].Equals(Tokens.False))
80-
|| (declaration.QualifiedModuleName.ComponentType == ComponentType.UserForm
81-
&& attribute.Values[0].Equals(Tokens.True));
82-
default:
83-
return false;
84-
}
64+
return Attributes.IsDefaultAttribute(declaration.QualifiedModuleName.ComponentType, attribute.Name, attribute.Values);
8565
}
8666

8767
private static bool MissesCorrespondingModuleAnnotation(Declaration declaration, AttributeNode attribute)
Lines changed: 47 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,47 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Concrete;
5+
using Rubberduck.Parsing.Annotations;
6+
using Rubberduck.Parsing.Inspections.Abstract;
7+
using Rubberduck.Parsing.Rewriter;
8+
using Rubberduck.Parsing.Symbols;
9+
using Rubberduck.Parsing.VBA;
10+
11+
namespace Rubberduck.Inspections.QuickFixes
12+
{
13+
public class AddAttributeAnnotationQuickFix : QuickFixBase
14+
{
15+
private readonly IAnnotationUpdater _annotationUpdater;
16+
private readonly IAttributeAnnotationProvider _attributeAnnotationProvider;
17+
18+
public AddAttributeAnnotationQuickFix(IAnnotationUpdater annotationUpdater, IAttributeAnnotationProvider attributeAnnotationProvider)
19+
: base(typeof(MissingModuleAnnotationInspection), typeof(MissingMemberAnnotationInspection))
20+
{
21+
_annotationUpdater = annotationUpdater;
22+
_attributeAnnotationProvider = attributeAnnotationProvider;
23+
}
24+
25+
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
26+
{
27+
var declaration = result.Target;
28+
string attributeName = result.Properties.AttributeName;
29+
IReadOnlyList<string> attributeValues = result.Properties.AttributeValues;
30+
var (annotationType, annotationValues) = declaration.DeclarationType.HasFlag(DeclarationType.Module)
31+
? _attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues)
32+
: _attributeAnnotationProvider.MemberAttributeAnnotation(AttributeBaseName(attributeName, declaration), attributeValues);
33+
_annotationUpdater.AddAnnotation(rewriteSession, declaration, annotationType, annotationValues);
34+
}
35+
36+
private static string AttributeBaseName(string attributeName, Declaration declaration)
37+
{
38+
return Attributes.AttributeBaseName(attributeName, declaration.IdentifierName);
39+
}
40+
41+
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.AddAttributeAnnotationQuickFix;
42+
43+
public override bool CanFixInProcedure => true;
44+
public override bool CanFixInModule => true;
45+
public override bool CanFixInProject => true;
46+
}
47+
}
Lines changed: 70 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,70 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Concrete;
5+
using Rubberduck.Parsing.Annotations;
6+
using Rubberduck.Parsing.Inspections.Abstract;
7+
using Rubberduck.Parsing.Rewriter;
8+
using Rubberduck.Parsing.Symbols;
9+
using Rubberduck.Parsing.VBA;
10+
using Rubberduck.VBEditor.SafeComWrappers;
11+
12+
namespace Rubberduck.Inspections.QuickFixes
13+
{
14+
public class AdjustAttributeAnnotationQuickFix : QuickFixBase
15+
{
16+
private readonly IAnnotationUpdater _annotationUpdater;
17+
private readonly IAttributeAnnotationProvider _attributeAnnotationProvider;
18+
19+
public AdjustAttributeAnnotationQuickFix(IAnnotationUpdater annotationUpdater, IAttributeAnnotationProvider attributeAnnotationProvider)
20+
: base(typeof(AttributeValueOutOfSyncInspection))
21+
{
22+
_annotationUpdater = annotationUpdater;
23+
_attributeAnnotationProvider = attributeAnnotationProvider;
24+
}
25+
26+
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
27+
{
28+
IAttributeAnnotation oldAnnotation = result.Properties.Annotation;
29+
string attributeName = result.Properties.AttributeName;
30+
IReadOnlyList<string> attributeValues = result.Properties.AttributeValues;
31+
32+
var declaration = result.Target;
33+
if (declaration.DeclarationType.HasFlag(DeclarationType.Module))
34+
{
35+
var componentType = declaration.QualifiedModuleName.ComponentType;
36+
if (IsDefaultAttribute(componentType, attributeName, attributeValues))
37+
{
38+
_annotationUpdater.RemoveAnnotation(rewriteSession, oldAnnotation);
39+
}
40+
else
41+
{
42+
var (newAnnotationType, newAnnotationValues) = _attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues);
43+
_annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotationType, newAnnotationValues);
44+
}
45+
}
46+
else
47+
{
48+
var attributeBaseName = AttributeBaseName(attributeName, declaration);
49+
var (newAnnotationType, newAnnotationValues) = _attributeAnnotationProvider.MemberAttributeAnnotation(attributeBaseName, attributeValues);
50+
_annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotationType, newAnnotationValues);
51+
}
52+
}
53+
54+
private static bool IsDefaultAttribute(ComponentType componentType, string attributeName, IReadOnlyList<string> attributeValues)
55+
{
56+
return Attributes.IsDefaultAttribute(componentType, attributeName, attributeValues);
57+
}
58+
59+
private static string AttributeBaseName(string attributeName, Declaration declaration)
60+
{
61+
return Attributes.AttributeBaseName(attributeName, declaration.IdentifierName);
62+
}
63+
64+
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.AdjustAttributeAnnotationQuickFix;
65+
66+
public override bool CanFixInProcedure => true;
67+
public override bool CanFixInModule => true;
68+
public override bool CanFixInProject => true;
69+
}
70+
}

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
}
Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,30 @@
1+
using Rubberduck.Inspections.Abstract;
2+
using Rubberduck.Inspections.Concrete;
3+
using Rubberduck.Parsing.Inspections.Abstract;
4+
using Rubberduck.Parsing.Rewriter;
5+
using Rubberduck.Parsing.VBA;
6+
7+
namespace Rubberduck.Inspections.QuickFixes
8+
{
9+
public sealed class RemoveAnnotationQuickFix : QuickFixBase
10+
{
11+
private readonly IAnnotationUpdater _annotationUpdater;
12+
13+
public RemoveAnnotationQuickFix(IAnnotationUpdater annotationUpdater)
14+
:base(typeof(MissingAttributeInspection))
15+
{
16+
_annotationUpdater = annotationUpdater;
17+
}
18+
19+
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
20+
{
21+
_annotationUpdater.RemoveAnnotation(rewriteSession, result.Properties.Annotation);
22+
}
23+
24+
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.RemoveAnnotationQuickFix;
25+
26+
public override bool CanFixInProcedure => false;
27+
public override bool CanFixInModule => false;
28+
public override bool CanFixInProject => false;
29+
}
30+
}

Rubberduck.CodeAnalysis/QuickFixes/RemoveAttributeQuickFix.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@ public class RemoveAttributeQuickFix : QuickFixBase
1414
private readonly IAttributesUpdater _attributesUpdater;
1515

1616
public RemoveAttributeQuickFix(IAttributesUpdater attributesUpdater)
17-
:base(typeof(AttributeValueOutOfSyncInspection))
17+
:base(typeof(MissingModuleAnnotationInspection), typeof(MissingMemberAnnotationInspection))
1818
{
1919
_attributesUpdater = attributesUpdater;
2020
}

0 commit comments

Comments
 (0)