Skip to content

Commit

Permalink
Add AdjustAttributeQuickFix
Browse files Browse the repository at this point in the history
This quickfix adjusts an attribute out of sync with a corresponding annotation to the value corresponding to the annotation.
  • Loading branch information
MDoerner committed Dec 17, 2018
1 parent 041c36a commit 991be9c
Show file tree
Hide file tree
Showing 6 changed files with 179 additions and 7 deletions.
Expand Up @@ -31,8 +31,11 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
if (HasDifferingAttributeValues(declaration, annotation, out var attributeValues))
{
var description = string.Format(InspectionResults.AttributeValueOutOfSyncInspection, declaration.IdentifierName,
annotation.Attribute, string.Join(", ", annotation.AttributeValues), string.Join(", ", attributeValues));
var description = string.Format(InspectionResults.AttributeValueOutOfSyncInspection,
annotation.Attribute,
string.Join(", ", attributeValues),
annotation.AnnotationType,
string.Join(", ", annotation.AttributeValues));

var result = new DeclarationInspectionResult(this, description, declaration,
new QualifiedContext(declaration.QualifiedModuleName, annotation.Context));
Expand Down
@@ -0,0 +1,45 @@
using System;
using System.Collections.Generic;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Concrete;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.Rewriter;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.Parsing;

namespace Rubberduck.Inspections.QuickFixes
{
public class AdjustAttributeValuesQuickFix : QuickFixBase
{
private readonly IAttributesUpdater _attributesUpdater;

public AdjustAttributeValuesQuickFix(IAttributesUpdater attributesUpdater)
: base(typeof(AttributeValueOutOfSyncInspection))
{
_attributesUpdater = attributesUpdater;
}

public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
{
var declaration = result.Target;
IAttributeAnnotation annotation = result.Properties.Annotation;
IReadOnlyList<string> attributeValues = result.Properties.AttributeValues;

var attributeName = declaration.DeclarationType.HasFlag(DeclarationType.Module)
? annotation.Attribute
: $"{declaration.IdentifierName}.{annotation.Attribute}";

_attributesUpdater.UpdateAttribute(rewriteSession, declaration, attributeName, annotation.AttributeValues, attributeValues);
}

public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.AdjustAttributeValuesQuickFix;

public override CodeKind TargetCodeKind => CodeKind.AttributesCode;

public override bool CanFixInProcedure => true;
public override bool CanFixInModule => true;
public override bool CanFixInProject => true;
}
}
15 changes: 12 additions & 3 deletions Rubberduck.Resources/Inspections/QuickFixes.Designer.cs

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

5 changes: 4 additions & 1 deletion Rubberduck.Resources/Inspections/QuickFixes.de.resx
Expand Up @@ -262,6 +262,9 @@
<value>'IsMissing'-Aufruf in Prüfung eines Standardwerts umschreiben.</value>
</data>
<data name="AddMissingAttributeQuickFix" xml:space="preserve">
<value>Füge das fehlende Attribut hinzu.</value>
<value>Fehlendes Attribut hinzufügen</value>
</data>
<data name="AdjustAttributeValuesQuickFix" xml:space="preserve">
<value>Attributwert(e) anpassen</value>
</data>
</root>
5 changes: 4 additions & 1 deletion Rubberduck.Resources/Inspections/QuickFixes.resx
Expand Up @@ -262,6 +262,9 @@
<value>Change 'IsMissing' call to test for default value.</value>
</data>
<data name="AddMissingAttributeQuickFix" xml:space="preserve">
<value>Add the missing attribute.</value>
<value>Add missing attribute</value>
</data>
<data name="AdjustAttributeValuesQuickFix" xml:space="preserve">
<value>Adjust attribute value(s)</value>
</data>
</root>
109 changes: 109 additions & 0 deletions RubberduckTests/QuickFixes/AdjustAttributeValuesQuickFixTests.cs
@@ -0,0 +1,109 @@
using NUnit.Framework;
using Rubberduck.Inspections.Concrete;
using Rubberduck.Inspections.QuickFixes;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.Parsing;

namespace RubberduckTests.QuickFixes
{
public class AdjustAttributeValuesQuickFixTests : QuickFixTestBase
{
[Test]
[Category("QuickFixes")]
public void ModuleAttributeOutOfSync_QuickFixWorks()
{
const string inputCode =
@"Attribute VB_Description = ""NotDesc""
'@ModuleAttribute VB_Description, ""Desc""
Public Sub Foo()
Const const1 As Integer = 9
End Sub";

const string expectedCode =
@"Attribute VB_Description = ""Desc""
'@ModuleAttribute VB_Description, ""Desc""
Public Sub Foo()
Const const1 As Integer = 9
End Sub";

var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new AttributeValueOutOfSyncInspection(state), CodeKind.AttributesCode);
Assert.AreEqual(expectedCode, actualCode);
}

[Test]
[Category("QuickFixes")]
public void VbExtKeyModuleAttributeOutOfSync_QuickFixWorks()
{
const string inputCode =
@"Attribute VB_Ext_Key = ""Key"", ""NotValue""
Attribute VB_Ext_Key = ""OtherKey"", ""OtherValue""
'@ModuleAttribute VB_Ext_Key, ""Key"", ""Value""
Public Sub Foo()
Const const1 As Integer = 9
End Sub";

const string expectedCode =
@"Attribute VB_Ext_Key = ""Key"", ""Value""
Attribute VB_Ext_Key = ""OtherKey"", ""OtherValue""
'@ModuleAttribute VB_Ext_Key, ""Key"", ""Value""
Public Sub Foo()
Const const1 As Integer = 9
End Sub";

var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new AttributeValueOutOfSyncInspection(state), CodeKind.AttributesCode);
Assert.AreEqual(expectedCode, actualCode);
}

[Test]
[Category("QuickFixes")]
public void MemberAttributeOutOfSync_QuickFixWorks()
{
const string inputCode =
@"'@MemberAttribute VB_Description, ""Desc""
Public Sub Foo()
Attribute Foo.VB_Description = ""NotDesc""
Const const1 As Integer = 9
End Sub";

const string expectedCode =
@"'@MemberAttribute VB_Description, ""Desc""
Public Sub Foo()
Attribute Foo.VB_Description = ""Desc""
Const const1 As Integer = 9
End Sub";

var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new AttributeValueOutOfSyncInspection(state), CodeKind.AttributesCode);
Assert.AreEqual(expectedCode, actualCode);
}

[Test]
[Category("QuickFixes")]
public void VbExtKeyMemberAttributeOutOfSync_QuickFixWorks()
{
const string inputCode =
@"'@MemberAttribute VB_Ext_Key, ""Key"", ""Value""
Public Sub Foo()
Attribute Foo.VB_Ext_Key = ""Key"", ""NotValue""
Attribute Foo.VB_Ext_Key = ""OtherKey"", ""OtherValue""
Const const1 As Integer = 9
End Sub";

const string expectedCode =
@"'@MemberAttribute VB_Ext_Key, ""Key"", ""Value""
Public Sub Foo()
Attribute Foo.VB_Ext_Key = ""Key"", ""Value""
Attribute Foo.VB_Ext_Key = ""OtherKey"", ""OtherValue""
Const const1 As Integer = 9
End Sub";

var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new AttributeValueOutOfSyncInspection(state), CodeKind.AttributesCode);
Assert.AreEqual(expectedCode, actualCode);
}

protected override IQuickFix QuickFix(RubberduckParserState state)
{
return new AdjustAttributeValuesQuickFix(new AttributesUpdater(state));
}
}
}

0 comments on commit 991be9c

Please sign in to comment.