Skip to content

Commit 4f5f532

Browse files
authored
Merge pull request #2148 from Hosch250/Issue2135
Fix Reorder Parameters refactoring bugs
2 parents 1847ab1 + 0eb2cf4 commit 4f5f532

File tree

2 files changed

+210
-51
lines changed

2 files changed

+210
-51
lines changed

RetailCoder.VBE/Refactorings/ReorderParameters/ReorderParametersRefactoring.cs

Lines changed: 54 additions & 50 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
using Rubberduck.Parsing;
55
using Rubberduck.Parsing.Grammar;
66
using Rubberduck.Parsing.Symbols;
7-
using Rubberduck.Parsing.VBA;
87
using Rubberduck.UI;
98
using Rubberduck.VBEditor;
109
using Rubberduck.VBEditor.Extensions;
@@ -106,70 +105,76 @@ private void AdjustReferences(IEnumerable<IdentifierReference> references)
106105
{
107106
foreach (var reference in references.Where(item => item.Context != _model.TargetDeclaration.Context))
108107
{
109-
dynamic proc = reference.Context;
110108
var module = reference.QualifiedModuleName.Component.CodeModule;
111109
VBAParser.ArgumentListContext argumentList = null;
112110
var callStmt = ParserRuleContextHelper.GetParent<VBAParser.CallStmtContext>(reference.Context);
113111
if (callStmt != null)
114112
{
115113
argumentList = CallStatement.GetArgumentList(callStmt);
116114
}
115+
116+
if (argumentList == null)
117+
{
118+
var indexExpression = ParserRuleContextHelper.GetParent<VBAParser.IndexExprContext>(reference.Context);
119+
if (indexExpression != null)
120+
{
121+
argumentList = ParserRuleContextHelper.GetChild<VBAParser.ArgumentListContext>(indexExpression);
122+
}
123+
}
124+
117125
if (argumentList == null) { continue; }
118126
RewriteCall(argumentList, module);
119127
}
120128
}
121129

122130
private void RewriteCall(VBAParser.ArgumentListContext paramList, CodeModule module)
123131
{
124-
List<string> paramNames = new List<string>();
132+
var argValues = new List<string>();
125133
if (paramList.positionalOrNamedArgumentList().positionalArgumentOrMissing() != null)
126134
{
127-
paramNames.AddRange(paramList.positionalOrNamedArgumentList().positionalArgumentOrMissing().Select(p =>
135+
argValues.AddRange(paramList.positionalOrNamedArgumentList().positionalArgumentOrMissing().Select(p =>
128136
{
129137
if (p is VBAParser.SpecifiedPositionalArgumentContext)
130138
{
131139
return ((VBAParser.SpecifiedPositionalArgumentContext)p).positionalArgument().GetText();
132140
}
133-
else
134-
{
135-
return string.Empty;
136-
}
141+
142+
return string.Empty;
137143
}).ToList());
138144
}
139145
if (paramList.positionalOrNamedArgumentList().namedArgumentList() != null)
140146
{
141-
paramNames.AddRange(paramList.positionalOrNamedArgumentList().namedArgumentList().namedArgument().Select(p => p.GetText()).ToList());
147+
argValues.AddRange(paramList.positionalOrNamedArgumentList().namedArgumentList().namedArgument().Select(p => p.GetText()).ToList());
142148
}
143149
if (paramList.positionalOrNamedArgumentList().requiredPositionalArgument() != null)
144150
{
145-
paramNames.Add(paramList.positionalOrNamedArgumentList().requiredPositionalArgument().GetText());
151+
argValues.Add(paramList.positionalOrNamedArgumentList().requiredPositionalArgument().GetText());
146152
}
147153

148154
var lineCount = paramList.Stop.Line - paramList.Start.Line + 1; // adjust for total line count
149155

150-
var newContent = module.Lines[paramList.Start.Line, lineCount].Replace(" _" + Environment.NewLine, string.Empty).RemoveExtraSpacesLeavingIndentation();
156+
var newContent = module.Lines[paramList.Start.Line, lineCount];
157+
newContent = newContent.Remove(paramList.Start.Column, paramList.GetText().Length);
151158

152-
var parameterIndex = 0;
153-
var currentStringIndex = 0;
154-
155-
for (var i = 0; i < paramNames.Count && parameterIndex < _model.Parameters.Count; i++)
159+
var reorderedArgValues = new List<string>();
160+
foreach (var param in _model.Parameters)
156161
{
157-
var parameterStringIndex = newContent.IndexOf(paramNames.ElementAt(i), currentStringIndex, StringComparison.Ordinal);
158-
159-
if (parameterStringIndex <= -1) { continue; }
160-
161-
var oldParameterString = paramNames.ElementAt(i);
162-
var newParameterString = paramNames.ElementAt(_model.Parameters.ElementAt(parameterIndex).Index);
163-
var beginningSub = newContent.Substring(0, parameterStringIndex);
164-
var replaceSub = newContent.Substring(parameterStringIndex).Replace(oldParameterString, newParameterString);
165-
166-
newContent = beginningSub + replaceSub;
162+
var argAtIndex = argValues.ElementAtOrDefault(param.Index);
163+
if (argAtIndex != null)
164+
{
165+
reorderedArgValues.Add(argAtIndex);
166+
}
167+
}
167168

168-
parameterIndex++;
169-
currentStringIndex = beginningSub.Length + newParameterString.Length;
169+
// property let/set and paramarrays
170+
for (var index = reorderedArgValues.Count; index < argValues.Count; index++)
171+
{
172+
reorderedArgValues.Add(argValues[index]);
170173
}
171174

172-
module.ReplaceLine(paramList.Start.Line, newContent);
175+
newContent = newContent.Insert(paramList.Start.Column, string.Join(", ", reorderedArgValues));
176+
177+
module.ReplaceLine(paramList.Start.Line, newContent.Replace(" _" + Environment.NewLine, string.Empty));
173178
module.DeleteLines(paramList.Start.Line + 1, lineCount - 1);
174179
}
175180

@@ -244,34 +249,33 @@ private void AdjustSignatures(Declaration declaration)
244249

245250
private void RewriteSignature(Declaration target, VBAParser.ArgListContext paramList, CodeModule module)
246251
{
247-
var argList = paramList.arg();
248-
249-
var newContent = GetOldSignature(target);
250-
var lineNum = paramList.GetSelection().LineCount;
252+
var parameters = paramList.arg().Select((s, i) => new {Index = i, Text = s.GetText()}).ToList();
251253

252-
var parameterIndex = 0;
253-
var currentStringIndex = 0;
254-
255-
for (var i = parameterIndex; i < _model.Parameters.Count; i++)
254+
var reorderedParams = new List<string>();
255+
foreach (var param in _model.Parameters)
256256
{
257-
var oldParam = argList.ElementAt(parameterIndex).GetText();
258-
var newParam = argList.ElementAt(_model.Parameters.ElementAt(parameterIndex).Index).GetText();
259-
var parameterStringIndex = newContent.IndexOf(oldParam, currentStringIndex, StringComparison.Ordinal);
260-
261-
if (parameterStringIndex > -1)
257+
var parameterAtIndex = parameters.SingleOrDefault(s => s.Index == param.Index);
258+
if (parameterAtIndex != null)
262259
{
263-
var beginningSub = newContent.Substring(0, parameterStringIndex);
264-
var replaceSub = newContent.Substring(parameterStringIndex).Replace(oldParam, newParam);
265-
266-
newContent = beginningSub + replaceSub;
267-
268-
parameterIndex++;
269-
currentStringIndex = beginningSub.Length + newParam.Length;
260+
reorderedParams.Add(parameterAtIndex.Text);
270261
}
271262
}
272263

273-
module.ReplaceLine(paramList.Start.Line, newContent.Replace(" _" + Environment.NewLine, string.Empty));
274-
module.DeleteLines(paramList.Start.Line + 1, lineNum - 1);
264+
// property let/set and paramarrays
265+
for (var index = reorderedParams.Count; index < parameters.Count; index++)
266+
{
267+
reorderedParams.Add(parameters[index].Text);
268+
}
269+
270+
var signature = GetOldSignature(target);
271+
signature = signature.Remove(signature.IndexOf('('));
272+
273+
var asTypeText = target.AsTypeContext == null ? string.Empty : " " + target.AsTypeContext.GetText();
274+
signature += '(' + string.Join(", ", reorderedParams) + ")" + (asTypeText == " " ? string.Empty : asTypeText);
275+
276+
var lineCount = paramList.GetSelection().LineCount;
277+
module.ReplaceLine(paramList.Start.Line, signature.Replace(" _" + Environment.NewLine, string.Empty));
278+
module.DeleteLines(paramList.Start.Line + 1, lineCount - 1);
275279
}
276280

277281
private string GetOldSignature(Declaration target)

RubberduckTests/Refactoring/ReorderParametersTests.cs

Lines changed: 156 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -65,6 +65,100 @@ public void ReorderParams_SwapPositions()
6565
Assert.AreEqual(expectedCode, module.Lines());
6666
}
6767

68+
[TestMethod]
69+
public void ReorderParams_SwapPositions_SignatureContainsParamName()
70+
{
71+
//Input
72+
const string inputCode =
73+
@"Private Sub Foo(a, ba)
74+
End Sub";
75+
var selection = new Selection(1, 16, 1, 16);
76+
77+
//Expectation
78+
const string expectedCode =
79+
@"Private Sub Foo(ba, a)
80+
End Sub";
81+
82+
//Arrange
83+
var builder = new MockVbeBuilder();
84+
VBComponent component;
85+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component, selection);
86+
var project = vbe.Object.VBProjects.Item(0);
87+
var module = project.VBComponents.Item(0).CodeModule;
88+
var mockHost = new Mock<IHostApplication>();
89+
mockHost.SetupAllProperties();
90+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
91+
92+
parser.Parse(new CancellationTokenSource());
93+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
94+
95+
var qualifiedSelection = new QualifiedSelection(new QualifiedModuleName(component), selection);
96+
97+
//set up model
98+
var model = new ReorderParametersModel(parser.State, qualifiedSelection, null);
99+
model.Parameters.Reverse();
100+
101+
var factory = SetupFactory(model);
102+
103+
//act
104+
var refactoring = new ReorderParametersRefactoring(vbe.Object, factory.Object, null);
105+
refactoring.Refactor(qualifiedSelection);
106+
107+
//assert
108+
Assert.AreEqual(expectedCode, module.Lines());
109+
}
110+
111+
[TestMethod]
112+
public void ReorderParams_SwapPositions_ReferenceValueContainsOtherReferenceValue()
113+
{
114+
//Input
115+
const string inputCode =
116+
@"Private Sub Foo(a, ba)
117+
End Sub
118+
119+
Sub Goo()
120+
Foo 1, 121
121+
End Sub";
122+
var selection = new Selection(1, 16, 1, 16);
123+
124+
//Expectation
125+
const string expectedCode =
126+
@"Private Sub Foo(ba, a)
127+
End Sub
128+
129+
Sub Goo()
130+
Foo 121, 1
131+
End Sub";
132+
133+
//Arrange
134+
var builder = new MockVbeBuilder();
135+
VBComponent component;
136+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component, selection);
137+
var project = vbe.Object.VBProjects.Item(0);
138+
var module = project.VBComponents.Item(0).CodeModule;
139+
var mockHost = new Mock<IHostApplication>();
140+
mockHost.SetupAllProperties();
141+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
142+
143+
parser.Parse(new CancellationTokenSource());
144+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
145+
146+
var qualifiedSelection = new QualifiedSelection(new QualifiedModuleName(component), selection);
147+
148+
//set up model
149+
var model = new ReorderParametersModel(parser.State, qualifiedSelection, null);
150+
model.Parameters.Reverse();
151+
152+
var factory = SetupFactory(model);
153+
154+
//act
155+
var refactoring = new ReorderParametersRefactoring(vbe.Object, factory.Object, null);
156+
refactoring.Refactor(qualifiedSelection);
157+
158+
//assert
159+
Assert.AreEqual(expectedCode, module.Lines());
160+
}
161+
68162
[TestMethod]
69163
public void ReorderParams_RefactorDeclaration()
70164
{
@@ -258,6 +352,67 @@ End Sub
258352
Assert.AreEqual(expectedCode, module.Lines());
259353
}
260354

355+
[TestMethod]
356+
public void RemoveParametersRefactoring_ClientReferencesAreUpdated_ParensAroundCall()
357+
{
358+
//Input
359+
const string inputCode =
360+
@"Private Sub bar()
361+
Dim x As Integer
362+
Dim y As Integer
363+
y = foo(x, 42)
364+
Debug.Print y, x
365+
End Sub
366+
367+
Private Function foo(ByRef a As Integer, ByVal b As Integer) As Integer
368+
a = b
369+
foo = a + b
370+
End Function";
371+
var selection = new Selection(8, 20, 8, 20);
372+
373+
//Expectation
374+
const string expectedCode =
375+
@"Private Sub bar()
376+
Dim x As Integer
377+
Dim y As Integer
378+
y = foo(42, x)
379+
Debug.Print y, x
380+
End Sub
381+
382+
Private Function foo(ByVal b As Integer, ByRef a As Integer) As Integer
383+
a = b
384+
foo = a + b
385+
End Function";
386+
387+
//Arrange
388+
var builder = new MockVbeBuilder();
389+
VBComponent component;
390+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component, selection);
391+
var project = vbe.Object.VBProjects.Item(0);
392+
var module = project.VBComponents.Item(0).CodeModule;
393+
var mockHost = new Mock<IHostApplication>();
394+
mockHost.SetupAllProperties();
395+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
396+
397+
parser.Parse(new CancellationTokenSource());
398+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
399+
400+
var qualifiedSelection = new QualifiedSelection(new QualifiedModuleName(component), selection);
401+
402+
//set up model
403+
var model = new ReorderParametersModel(parser.State, qualifiedSelection, null);
404+
model.Parameters.Reverse();
405+
406+
var factory = SetupFactory(model);
407+
408+
//act
409+
var refactoring = new ReorderParametersRefactoring(vbe.Object, factory.Object, null);
410+
refactoring.Refactor(qualifiedSelection);
411+
412+
//assert
413+
Assert.AreEqual(expectedCode, module.Lines());
414+
}
415+
261416
[TestMethod]
262417
public void ReorderParametersRefactoring_ReorderNamedParams()
263418
{
@@ -634,7 +789,7 @@ public void ReorderParametersRefactoring_SignatureOnMultipleLines()
634789

635790
//Expectation
636791
const string expectedCode =
637-
@"Private Sub Foo(ByVal arg3 As Date, ByVal arg2 As String, ByVal arg1 As Integer)
792+
@"Private Sub Foo(ByVal arg3 As Date, ByVal arg2 As String, ByVal arg1 As Integer)
638793
End Sub"; // note: IDE removes excess spaces
639794

640795
//Arrange

0 commit comments

Comments
 (0)