Skip to content

Commit 991be9c

Browse files
committed
Add AdjustAttributeQuickFix
This quickfix adjusts an attribute out of sync with a corresponding annotation to the value corresponding to the annotation.
1 parent 041c36a commit 991be9c

File tree

6 files changed

+179
-7
lines changed

6 files changed

+179
-7
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,8 +31,11 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3131
{
3232
if (HasDifferingAttributeValues(declaration, annotation, out var attributeValues))
3333
{
34-
var description = string.Format(InspectionResults.AttributeValueOutOfSyncInspection, declaration.IdentifierName,
35-
annotation.Attribute, string.Join(", ", annotation.AttributeValues), string.Join(", ", attributeValues));
34+
var description = string.Format(InspectionResults.AttributeValueOutOfSyncInspection,
35+
annotation.Attribute,
36+
string.Join(", ", attributeValues),
37+
annotation.AnnotationType,
38+
string.Join(", ", annotation.AttributeValues));
3639

3740
var result = new DeclarationInspectionResult(this, description, declaration,
3841
new QualifiedContext(declaration.QualifiedModuleName, annotation.Context));
Lines changed: 45 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,45 @@
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.Parsing.VBA.Parsing;
11+
12+
namespace Rubberduck.Inspections.QuickFixes
13+
{
14+
public class AdjustAttributeValuesQuickFix : QuickFixBase
15+
{
16+
private readonly IAttributesUpdater _attributesUpdater;
17+
18+
public AdjustAttributeValuesQuickFix(IAttributesUpdater attributesUpdater)
19+
: base(typeof(AttributeValueOutOfSyncInspection))
20+
{
21+
_attributesUpdater = attributesUpdater;
22+
}
23+
24+
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
25+
{
26+
var declaration = result.Target;
27+
IAttributeAnnotation annotation = result.Properties.Annotation;
28+
IReadOnlyList<string> attributeValues = result.Properties.AttributeValues;
29+
30+
var attributeName = declaration.DeclarationType.HasFlag(DeclarationType.Module)
31+
? annotation.Attribute
32+
: $"{declaration.IdentifierName}.{annotation.Attribute}";
33+
34+
_attributesUpdater.UpdateAttribute(rewriteSession, declaration, attributeName, annotation.AttributeValues, attributeValues);
35+
}
36+
37+
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.AdjustAttributeValuesQuickFix;
38+
39+
public override CodeKind TargetCodeKind => CodeKind.AttributesCode;
40+
41+
public override bool CanFixInProcedure => true;
42+
public override bool CanFixInModule => true;
43+
public override bool CanFixInProject => true;
44+
}
45+
}

Rubberduck.Resources/Inspections/QuickFixes.Designer.cs

Lines changed: 12 additions & 3 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Resources/Inspections/QuickFixes.de.resx

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -262,6 +262,9 @@
262262
<value>'IsMissing'-Aufruf in Prüfung eines Standardwerts umschreiben.</value>
263263
</data>
264264
<data name="AddMissingAttributeQuickFix" xml:space="preserve">
265-
<value>Füge das fehlende Attribut hinzu.</value>
265+
<value>Fehlendes Attribut hinzufügen</value>
266+
</data>
267+
<data name="AdjustAttributeValuesQuickFix" xml:space="preserve">
268+
<value>Attributwert(e) anpassen</value>
266269
</data>
267270
</root>

Rubberduck.Resources/Inspections/QuickFixes.resx

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -262,6 +262,9 @@
262262
<value>Change 'IsMissing' call to test for default value.</value>
263263
</data>
264264
<data name="AddMissingAttributeQuickFix" xml:space="preserve">
265-
<value>Add the missing attribute.</value>
265+
<value>Add missing attribute</value>
266+
</data>
267+
<data name="AdjustAttributeValuesQuickFix" xml:space="preserve">
268+
<value>Adjust attribute value(s)</value>
266269
</data>
267270
</root>
Lines changed: 109 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,109 @@
1+
using NUnit.Framework;
2+
using Rubberduck.Inspections.Concrete;
3+
using Rubberduck.Inspections.QuickFixes;
4+
using Rubberduck.Parsing.Inspections.Abstract;
5+
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.Parsing.VBA.Parsing;
7+
8+
namespace RubberduckTests.QuickFixes
9+
{
10+
public class AdjustAttributeValuesQuickFixTests : QuickFixTestBase
11+
{
12+
[Test]
13+
[Category("QuickFixes")]
14+
public void ModuleAttributeOutOfSync_QuickFixWorks()
15+
{
16+
const string inputCode =
17+
@"Attribute VB_Description = ""NotDesc""
18+
'@ModuleAttribute VB_Description, ""Desc""
19+
Public Sub Foo()
20+
Const const1 As Integer = 9
21+
End Sub";
22+
23+
const string expectedCode =
24+
@"Attribute VB_Description = ""Desc""
25+
'@ModuleAttribute VB_Description, ""Desc""
26+
Public Sub Foo()
27+
Const const1 As Integer = 9
28+
End Sub";
29+
30+
var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new AttributeValueOutOfSyncInspection(state), CodeKind.AttributesCode);
31+
Assert.AreEqual(expectedCode, actualCode);
32+
}
33+
34+
[Test]
35+
[Category("QuickFixes")]
36+
public void VbExtKeyModuleAttributeOutOfSync_QuickFixWorks()
37+
{
38+
const string inputCode =
39+
@"Attribute VB_Ext_Key = ""Key"", ""NotValue""
40+
Attribute VB_Ext_Key = ""OtherKey"", ""OtherValue""
41+
'@ModuleAttribute VB_Ext_Key, ""Key"", ""Value""
42+
Public Sub Foo()
43+
Const const1 As Integer = 9
44+
End Sub";
45+
46+
const string expectedCode =
47+
@"Attribute VB_Ext_Key = ""Key"", ""Value""
48+
Attribute VB_Ext_Key = ""OtherKey"", ""OtherValue""
49+
'@ModuleAttribute VB_Ext_Key, ""Key"", ""Value""
50+
Public Sub Foo()
51+
Const const1 As Integer = 9
52+
End Sub";
53+
54+
var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new AttributeValueOutOfSyncInspection(state), CodeKind.AttributesCode);
55+
Assert.AreEqual(expectedCode, actualCode);
56+
}
57+
58+
[Test]
59+
[Category("QuickFixes")]
60+
public void MemberAttributeOutOfSync_QuickFixWorks()
61+
{
62+
const string inputCode =
63+
@"'@MemberAttribute VB_Description, ""Desc""
64+
Public Sub Foo()
65+
Attribute Foo.VB_Description = ""NotDesc""
66+
Const const1 As Integer = 9
67+
End Sub";
68+
69+
const string expectedCode =
70+
@"'@MemberAttribute VB_Description, ""Desc""
71+
Public Sub Foo()
72+
Attribute Foo.VB_Description = ""Desc""
73+
Const const1 As Integer = 9
74+
End Sub";
75+
76+
var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new AttributeValueOutOfSyncInspection(state), CodeKind.AttributesCode);
77+
Assert.AreEqual(expectedCode, actualCode);
78+
}
79+
80+
[Test]
81+
[Category("QuickFixes")]
82+
public void VbExtKeyMemberAttributeOutOfSync_QuickFixWorks()
83+
{
84+
const string inputCode =
85+
@"'@MemberAttribute VB_Ext_Key, ""Key"", ""Value""
86+
Public Sub Foo()
87+
Attribute Foo.VB_Ext_Key = ""Key"", ""NotValue""
88+
Attribute Foo.VB_Ext_Key = ""OtherKey"", ""OtherValue""
89+
Const const1 As Integer = 9
90+
End Sub";
91+
92+
const string expectedCode =
93+
@"'@MemberAttribute VB_Ext_Key, ""Key"", ""Value""
94+
Public Sub Foo()
95+
Attribute Foo.VB_Ext_Key = ""Key"", ""Value""
96+
Attribute Foo.VB_Ext_Key = ""OtherKey"", ""OtherValue""
97+
Const const1 As Integer = 9
98+
End Sub";
99+
100+
var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new AttributeValueOutOfSyncInspection(state), CodeKind.AttributesCode);
101+
Assert.AreEqual(expectedCode, actualCode);
102+
}
103+
104+
protected override IQuickFix QuickFix(RubberduckParserState state)
105+
{
106+
return new AdjustAttributeValuesQuickFix(new AttributesUpdater(state));
107+
}
108+
}
109+
}

0 commit comments

Comments
 (0)