Skip to content

Commit 596870a

Browse files
committed
Fix bug in Convert Function/Property Get to Procedure quick fix
1 parent cef981b commit 596870a

File tree

6 files changed

+85
-56
lines changed

6 files changed

+85
-56
lines changed

RetailCoder.VBE/Inspections/ConvertToProcedureQuickFix.cs

Lines changed: 31 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -6,24 +6,18 @@
66
using System.Collections.Generic;
77
using System.Linq;
88
using System.Text.RegularExpressions;
9-
using Microsoft.Vbe.Interop;
109
using Rubberduck.Parsing.Symbols;
1110

1211
namespace Rubberduck.Inspections
1312
{
1413
public class ConvertToProcedureQuickFix : CodeInspectionQuickFix
1514
{
16-
private readonly IEnumerable<string> _returnStatements;
15+
private readonly Declaration _target;
1716

18-
public ConvertToProcedureQuickFix(ParserRuleContext context, QualifiedSelection selection)
19-
: this(context, selection, new List<string>())
20-
{
21-
}
22-
23-
public ConvertToProcedureQuickFix(ParserRuleContext context, QualifiedSelection selection, IEnumerable<string> returnStatements)
17+
public ConvertToProcedureQuickFix(ParserRuleContext context, QualifiedSelection selection, Declaration target)
2418
: base(context, selection, InspectionsUI.ConvertFunctionToProcedureQuickFix)
2519
{
26-
_returnStatements = returnStatements;
20+
_target = target;
2721
}
2822

2923
public override void Fix()
@@ -37,47 +31,53 @@ public override void Fix()
3731
throw new InvalidOperationException(string.Format(InspectionsUI.InvalidContextTypeInspectionFix, Context.GetType(), GetType()));
3832
}
3933

34+
var functionName = Context is VBAParser.FunctionStmtContext
35+
? ((VBAParser.FunctionStmtContext) Context).functionName()
36+
: ((VBAParser.PropertyGetStmtContext) Context).functionName();
4037

41-
VBAParser.FunctionNameContext functionName = null;
42-
if (Context is VBAParser.FunctionStmtContext)
43-
{
44-
functionName = ((VBAParser.FunctionStmtContext)Context).functionName();
45-
}
46-
else
47-
{
48-
functionName = ((VBAParser.PropertyGetStmtContext)Context).functionName();
49-
}
50-
51-
string token = functionContext != null
38+
var token = functionContext != null
5239
? Tokens.Function
5340
: Tokens.Property + ' ' + Tokens.Get;
54-
string endToken = token == Tokens.Function
41+
var endToken = token == Tokens.Function
5542
? token
5643
: Tokens.Property;
5744

5845
string visibility = context.visibility() == null ? string.Empty : context.visibility().GetText() + ' ';
59-
string name = ' ' + Identifier.GetName(functionName.identifier());
60-
bool hasTypeHint = Identifier.GetTypeHintValue(functionName.identifier()) != null;
46+
var name = ' ' + Identifier.GetName(functionName.identifier());
47+
var hasTypeHint = Identifier.GetTypeHintValue(functionName.identifier()) != null;
6148

6249
string args = context.argList().GetText();
6350
string asType = context.asTypeClause() == null ? string.Empty : ' ' + context.asTypeClause().GetText();
6451

65-
string oldSignature = visibility + token + name + (hasTypeHint ? Identifier.GetTypeHintValue(functionName.identifier()) : string.Empty) + args + asType;
66-
string newSignature = visibility + Tokens.Sub + name + args;
52+
var oldSignature = visibility + token + name + (hasTypeHint ? Identifier.GetTypeHintValue(functionName.identifier()) : string.Empty) + args + asType;
53+
var newSignature = visibility + Tokens.Sub + name + args;
6754

68-
string procedure = Context.GetText();
69-
string noReturnStatements = procedure;
70-
_returnStatements.ToList().ForEach(returnStatement =>
55+
var procedure = Context.GetText();
56+
var noReturnStatements = procedure;
57+
58+
GetReturnStatements(_target).ToList().ForEach(returnStatement =>
7159
noReturnStatements = Regex.Replace(noReturnStatements, @"[ \t\f]*" + returnStatement + @"[ \t\f]*\r?\n?", ""));
72-
string result = noReturnStatements.Replace(oldSignature, newSignature)
60+
var result = noReturnStatements.Replace(oldSignature, newSignature)
7361
.Replace(Tokens.End + ' ' + endToken, Tokens.End + ' ' + Tokens.Sub)
7462
.Replace(Tokens.Exit + ' ' + endToken, Tokens.Exit + ' ' + Tokens.Sub);
7563

76-
CodeModule module = Selection.QualifiedName.Component.CodeModule;
77-
Selection selection = Context.GetSelection();
64+
var module = Selection.QualifiedName.Component.CodeModule;
65+
var selection = Context.GetSelection();
7866

7967
module.DeleteLines(selection.StartLine, selection.LineCount);
8068
module.InsertLines(selection.StartLine, result);
8169
}
70+
71+
private IEnumerable<string> GetReturnStatements(Declaration declaration)
72+
{
73+
return declaration.References
74+
.Where(usage => IsReturnStatement(declaration, usage))
75+
.Select(usage => usage.Context.Parent.GetText());
76+
}
77+
78+
private bool IsReturnStatement(Declaration declaration, IdentifierReference assignment)
79+
{
80+
return assignment.ParentScoping.Equals(declaration) && assignment.Declaration.Equals(declaration);
81+
}
8282
}
8383
}

RetailCoder.VBE/Inspections/FunctionReturnValueNotUsedInspection.cs

Lines changed: 2 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -46,11 +46,10 @@ private IEnumerable<FunctionReturnValueNotUsedInspectionResult> GetInterfaceMemb
4646
implementationMember =>
4747
Tuple.Create(implementationMember.Context,
4848
new QualifiedSelection(implementationMember.QualifiedName.QualifiedModuleName,
49-
implementationMember.Selection), GetReturnStatements(implementationMember)))
49+
implementationMember.Selection), implementationMember))
5050
select
5151
new FunctionReturnValueNotUsedInspectionResult(this, interfaceMember.Context,
52-
interfaceMember.QualifiedName, GetReturnStatements(interfaceMember),
53-
implementationMemberIssues, interfaceMember);
52+
interfaceMember.QualifiedName, implementationMemberIssues, interfaceMember);
5453
}
5554

5655
private IEnumerable<FunctionReturnValueNotUsedInspectionResult> GetNonInterfaceIssues(IEnumerable<Declaration> nonInterfaceFunctions)
@@ -62,18 +61,10 @@ private IEnumerable<FunctionReturnValueNotUsedInspectionResult> GetNonInterfaceI
6261
this,
6362
function.Context,
6463
function.QualifiedName,
65-
GetReturnStatements(function),
6664
function));
6765
return nonInterfaceIssues;
6866
}
6967

70-
private IEnumerable<string> GetReturnStatements(Declaration function)
71-
{
72-
return function.References
73-
.Where(usage => IsReturnStatement(function, usage))
74-
.Select(usage => usage.Context.Parent.Parent.Parent.GetText());
75-
}
76-
7768
private bool IsReturnValueUsed(Declaration function)
7869
{
7970
foreach (var usage in function.References)

RetailCoder.VBE/Inspections/FunctionReturnValueNotUsedInspectionResult.cs

Lines changed: 3 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -16,22 +16,20 @@ public FunctionReturnValueNotUsedInspectionResult(
1616
IInspection inspection,
1717
ParserRuleContext context,
1818
QualifiedMemberName qualifiedName,
19-
IEnumerable<string> returnStatements,
2019
Declaration target)
21-
: this(inspection, context, qualifiedName, returnStatements, new List<Tuple<ParserRuleContext, QualifiedSelection, IEnumerable<string>>>(), target)
20+
: this(inspection, context, qualifiedName, new List<Tuple<ParserRuleContext, QualifiedSelection, Declaration>>(), target)
2221
{
2322
}
2423

2524
public FunctionReturnValueNotUsedInspectionResult(
2625
IInspection inspection,
2726
ParserRuleContext context,
2827
QualifiedMemberName qualifiedName,
29-
IEnumerable<string> returnStatements,
30-
IEnumerable<Tuple<ParserRuleContext, QualifiedSelection, IEnumerable<string>>> children,
28+
IEnumerable<Tuple<ParserRuleContext, QualifiedSelection, Declaration>> children,
3129
Declaration target)
3230
: base(inspection, qualifiedName.QualifiedModuleName, context, target)
3331
{
34-
var root = new ConvertToProcedureQuickFix(context, QualifiedSelection, returnStatements);
32+
var root = new ConvertToProcedureQuickFix(context, QualifiedSelection, target);
3533
var compositeFix = new CompositeCodeInspectionFix(root);
3634
children.ToList().ForEach(child => compositeFix.AddChild(new ConvertToProcedureQuickFix(child.Item1, child.Item2, child.Item3)));
3735
_quickFixes = new CodeInspectionQuickFix[]

RetailCoder.VBE/Inspections/NonReturningFunctionInspectionResult.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ public NonReturningFunctionInspectionResult(IInspection inspection,
2020
? new CodeInspectionQuickFix[] { }
2121
: new CodeInspectionQuickFix[]
2222
{
23-
new ConvertToProcedureQuickFix(Context, QualifiedSelection),
23+
new ConvertToProcedureQuickFix(Context, QualifiedSelection, target),
2424
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName),
2525
};
2626
}

RetailCoder.VBE/Sinks.cs

Lines changed: 0 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -227,7 +227,6 @@ private void ComponentsSink_ComponentAdded(object sender, DispatcherEventArgs<VB
227227
if (!ComponentSinksEnabled) { return; }
228228

229229
var projectId = e.Item.Collection.Parent.HelpFile;
230-
var componentName = e.Item.Name;
231230

232231
var handler = ComponentAdded;
233232
if (handler != null)
@@ -241,7 +240,6 @@ private void ComponentsSink_ComponentReloaded(object sender, DispatcherEventArgs
241240
if (!ComponentSinksEnabled) { return; }
242241

243242
var projectId = e.Item.Collection.Parent.HelpFile;
244-
var componentName = e.Item.Name;
245243

246244
var handler = ComponentReloaded;
247245
if (handler != null)
@@ -255,7 +253,6 @@ private void ComponentsSink_ComponentRemoved(object sender, DispatcherEventArgs<
255253
if (!ComponentSinksEnabled) { return; }
256254

257255
var projectId = e.Item.Collection.Parent.HelpFile;
258-
var componentName = e.Item.Name;
259256

260257
var handler = ComponentRemoved;
261258
if (handler != null)
@@ -269,8 +266,6 @@ private void ComponentsSink_ComponentRenamed(object sender, DispatcherRenamedEve
269266
if (!ComponentSinksEnabled) { return; }
270267

271268
var projectId = e.Item.Collection.Parent.HelpFile;
272-
var componentName = e.Item.Name;
273-
var oldName = e.OldName;
274269

275270
var handler = ComponentRenamed;
276271
if (handler != null)
@@ -284,7 +279,6 @@ private void ComponentsSink_ComponentSelected(object sender, DispatcherEventArgs
284279
if (!ComponentSinksEnabled) { return; }
285280

286281
var projectId = e.Item.Collection.Parent.HelpFile;
287-
var componentName = e.Item.Name;
288282

289283
var handler = ComponentSelected;
290284
if (handler != null)

RubberduckTests/Inspections/FunctionReturnValueNotUsedInspectionTests.cs

Lines changed: 48 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -483,8 +483,54 @@ End If
483483
const string expectedCode =
484484
@"Public Sub Foo(ByVal bar As String)
485485
If True Then
486-
Else
487-
End If
486+
Else
487+
End If
488+
End Sub";
489+
490+
//Arrange
491+
var builder = new MockVbeBuilder();
492+
VBComponent component;
493+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
494+
var project = vbe.Object.VBProjects.Item(0);
495+
var module = project.VBComponents.Item(0).CodeModule;
496+
var mockHost = new Mock<IHostApplication>();
497+
mockHost.SetupAllProperties();
498+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
499+
500+
parser.Parse(new CancellationTokenSource());
501+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
502+
503+
var inspection = new FunctionReturnValueNotUsedInspection(parser.State);
504+
var inspectionResults = inspection.GetInspectionResults();
505+
506+
inspectionResults.First().QuickFixes.First().Fix();
507+
508+
string actual = module.Lines();
509+
Assert.AreEqual(expectedCode, actual);
510+
}
511+
512+
[TestMethod]
513+
public void FunctionReturnValueNotUsed_QuickFixWorks_NoInterface_ManyBodyStatements()
514+
{
515+
const string inputCode =
516+
@"Function foo(ByRef fizz As Boolean) As Boolean
517+
fizz = True
518+
goo
519+
label1:
520+
foo = fizz
521+
End Function
522+
523+
Sub goo()
524+
End Sub";
525+
526+
const string expectedCode =
527+
@"Sub foo(ByRef fizz As Boolean)
528+
fizz = True
529+
goo
530+
label1:
531+
End Sub
532+
533+
Sub goo()
488534
End Sub";
489535

490536
//Arrange

0 commit comments

Comments
 (0)