Skip to content

Commit

Permalink
Merge pull request #2150 from Hosch250/Issue2135
Browse files Browse the repository at this point in the history
Give Write Only Property a custom quick fix
  • Loading branch information
Hosch250 committed Jul 27, 2016
2 parents bbeaffb + 2320149 commit c2d0696
Show file tree
Hide file tree
Showing 6 changed files with 164 additions and 2 deletions.
12 changes: 11 additions & 1 deletion RetailCoder.VBE/Inspections/InspectionsUI.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 RetailCoder.VBE/Inspections/InspectionsUI.resx
Expand Up @@ -565,4 +565,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu
<data name="MalformedAnnotationInspectionResultFormat" xml:space="preserve">
<value>Malformed '{0}' annotation.</value>
</data>
</root>
<data name="WriteOnlyPropertyQuickFix" xml:space="preserve">
<value>Add property get</value>
</data>
</root>
1 change: 1 addition & 0 deletions RetailCoder.VBE/Inspections/WriteOnlyPropertyInspection.cs
Expand Up @@ -54,6 +54,7 @@ public override IEnumerable<CodeInspectionQuickFix> QuickFixes
{
return new CodeInspectionQuickFix[]
{
new WriteOnlyPropertyQuickFix(Context, Target),
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName)
};
}
Expand Down
36 changes: 36 additions & 0 deletions RetailCoder.VBE/Inspections/WriteOnlyPropertyQuickFix.cs
@@ -0,0 +1,36 @@
using System;
using System.Linq;
using Antlr4.Runtime;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;

namespace Rubberduck.Inspections
{
public class WriteOnlyPropertyQuickFix : CodeInspectionQuickFix
{
private readonly Declaration _target;

public WriteOnlyPropertyQuickFix(ParserRuleContext context, Declaration target)
: base(context, target.QualifiedSelection, InspectionsUI.WriteOnlyPropertyQuickFix)
{
_target = target;
}

public override void Fix()
{
var parameters = ((IDeclarationWithParameter) _target).Parameters.Cast<ParameterDeclaration>().ToList();

var signatureParams = parameters.Except(new[] {parameters.Last()}).Select(GetParamText);
var propertyGet = "Public Property Get " + _target.IdentifierName + "(" + string.Join(", ", signatureParams) +
") As " + parameters.Last().AsTypeName + Environment.NewLine + "End Property";

var module = _target.QualifiedName.QualifiedModuleName.Component.CodeModule;
module.InsertLines(_target.Selection.StartLine, propertyGet);
}

private string GetParamText(ParameterDeclaration param)
{
return (((VBAParser.ArgContext)param.Context).BYVAL() == null ? "ByRef " : "ByVal ") + param.IdentifierName + " As " + param.AsTypeName;
}
}
}
1 change: 1 addition & 0 deletions RetailCoder.VBE/Rubberduck.csproj
Expand Up @@ -369,6 +369,7 @@
<Compile Include="Inspections\MalformedAnnotationInspection.cs" />
<Compile Include="Inspections\ObjectVariableNotSetInspection.cs" />
<Compile Include="Inspections\RemoveExplicitCallStatmentQuickFix.cs" />
<Compile Include="Inspections\WriteOnlyPropertyQuickFix.cs" />
<Compile Include="Navigation\CodeExplorer\ICodeExplorerDeclarationViewModel.cs" />
<Compile Include="Navigation\Folders\FolderHelper.cs" />
<Compile Include="Refactorings\ExtractMethod\ExtractedMethod.cs" />
Expand Down
111 changes: 111 additions & 0 deletions RubberduckTests/Inspections/WriteOnlyPropertyInspectionTests.cs
Expand Up @@ -193,6 +193,117 @@ public void WriteOnlyProperty_Ignored_DoesNotReturnResult()
Assert.IsFalse(inspectionResults.Any());
}

[TestMethod]
[TestCategory("Inspections")]
public void WriteOnlyProperty_AddPropertyGetQuickFixWorks_ImplicitTypesAndAccessibility()
{
const string inputCode =
@"Property Let Foo(value)
End Property";

const string expectedCode =
@"Public Property Get Foo() As Variant
End Property
Property Let Foo(value)
End Property";

//Arrange
var builder = new MockVbeBuilder();
var project = builder.ProjectBuilder("VBAProject", vbext_ProjectProtection.vbext_pp_none)
.AddComponent("MyClass", vbext_ComponentType.vbext_ct_ClassModule, inputCode)
.Build();
var module = project.Object.VBComponents.Item(0).CodeModule;
var vbe = builder.AddProject(project).Build();

var mockHost = new Mock<IHostApplication>();
mockHost.SetupAllProperties();
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));

parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

var inspection = new WriteOnlyPropertyInspection(parser.State);
var inspectionResults = inspection.GetInspectionResults();

inspectionResults.First().QuickFixes.Single(s => s is WriteOnlyPropertyQuickFix).Fix();

Assert.AreEqual(expectedCode, module.Lines());
}

[TestMethod]
[TestCategory("Inspections")]
public void WriteOnlyProperty_AddPropertyGetQuickFixWorks_ExlicitTypesAndAccessibility()
{
const string inputCode =
@"Public Property Let Foo(ByVal value As Integer)
End Property";

const string expectedCode =
@"Public Property Get Foo() As Integer
End Property
Public Property Let Foo(ByVal value As Integer)
End Property";

//Arrange
var builder = new MockVbeBuilder();
var project = builder.ProjectBuilder("VBAProject", vbext_ProjectProtection.vbext_pp_none)
.AddComponent("MyClass", vbext_ComponentType.vbext_ct_ClassModule, inputCode)
.Build();
var module = project.Object.VBComponents.Item(0).CodeModule;
var vbe = builder.AddProject(project).Build();

var mockHost = new Mock<IHostApplication>();
mockHost.SetupAllProperties();
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));

parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

var inspection = new WriteOnlyPropertyInspection(parser.State);
var inspectionResults = inspection.GetInspectionResults();

inspectionResults.First().QuickFixes.Single(s => s is WriteOnlyPropertyQuickFix).Fix();

Assert.AreEqual(expectedCode, module.Lines());
}

[TestMethod]
[TestCategory("Inspections")]
public void WriteOnlyProperty_AddPropertyGetQuickFixWorks_MultipleParams()
{
const string inputCode =
@"Public Property Let Foo(value1, ByVal value2 As Integer, ByRef value3 As Long, value4 As Date, ByVal value5, value6 As String)
End Property";

const string expectedCode =
@"Public Property Get Foo(ByRef value1 As Variant, ByVal value2 As Integer, ByRef value3 As Long, ByRef value4 As Date, ByVal value5 As Variant) As String
End Property
Public Property Let Foo(value1, ByVal value2 As Integer, ByRef value3 As Long, value4 As Date, ByVal value5, value6 As String)
End Property";

//Arrange
var builder = new MockVbeBuilder();
var project = builder.ProjectBuilder("VBAProject", vbext_ProjectProtection.vbext_pp_none)
.AddComponent("MyClass", vbext_ComponentType.vbext_ct_ClassModule, inputCode)
.Build();
var module = project.Object.VBComponents.Item(0).CodeModule;
var vbe = builder.AddProject(project).Build();

var mockHost = new Mock<IHostApplication>();
mockHost.SetupAllProperties();
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));

parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

var inspection = new WriteOnlyPropertyInspection(parser.State);
var inspectionResults = inspection.GetInspectionResults();

inspectionResults.First().QuickFixes.Single(s => s is WriteOnlyPropertyQuickFix).Fix();

Assert.AreEqual(expectedCode, module.Lines());
}

[TestMethod]
[TestCategory("Inspections")]
public void WriteOnlyProperty_IgnoreQuickFixWorks()
Expand Down

0 comments on commit c2d0696

Please sign in to comment.