Skip to content

Commit 86d006b

Browse files
committed
Fix bugs in generated remove params callers
1 parent c3a506e commit 86d006b

File tree

2 files changed

+148
-67
lines changed

2 files changed

+148
-67
lines changed

RetailCoder.VBE/Refactorings/RemoveParameters/RemoveParametersRefactoring.cs

Lines changed: 33 additions & 58 deletions
Original file line numberDiff line numberDiff line change
@@ -96,7 +96,6 @@ private void AdjustReferences(IEnumerable<IdentifierReference> references, Decla
9696
{
9797
foreach (var reference in references.Where(item => item.Context != method.Context))
9898
{
99-
var proc = (dynamic)reference.Context;
10099
var module = reference.QualifiedModuleName.Component.CodeModule;
101100
VBAParser.ArgumentListContext argumentList = null;
102101
var callStmt = ParserRuleContextHelper.GetParent<VBAParser.CallStmtContext>(reference.Context);
@@ -111,7 +110,7 @@ private void AdjustReferences(IEnumerable<IdentifierReference> references, Decla
111110

112111
private void RemoveCallParameter(VBAParser.ArgumentListContext paramList, CodeModule module)
113112
{
114-
List<string> paramNames = new List<string>();
113+
var paramNames = new List<string>();
115114
if (paramList.positionalOrNamedArgumentList().positionalArgumentOrMissing() != null)
116115
{
117116
paramNames.AddRange(paramList.positionalOrNamedArgumentList().positionalArgumentOrMissing().Select(p =>
@@ -120,10 +119,8 @@ private void RemoveCallParameter(VBAParser.ArgumentListContext paramList, CodeMo
120119
{
121120
return ((VBAParser.SpecifiedPositionalArgumentContext)p).positionalArgument().GetText();
122121
}
123-
else
124-
{
125-
return string.Empty;
126-
}
122+
123+
return string.Empty;
127124
}).ToList());
128125
}
129126
if (paramList.positionalOrNamedArgumentList().namedArgumentList() != null)
@@ -136,48 +133,46 @@ private void RemoveCallParameter(VBAParser.ArgumentListContext paramList, CodeMo
136133
}
137134
var lineCount = paramList.Stop.Line - paramList.Start.Line + 1; // adjust for total line count
138135

139-
var newContent = module.Lines[paramList.Start.Line, lineCount].Replace(" _" + Environment.NewLine, string.Empty).RemoveExtraSpacesLeavingIndentation();
140-
var currentStringIndex = 0;
136+
var newContent = module.Lines[paramList.Start.Line, lineCount];
137+
newContent = newContent.Remove(paramList.Start.Column, paramList.GetText().Length);
141138

142-
foreach (
143-
var param in
144-
_model.Parameters.Where(item => item.IsRemoved && item.Index < paramNames.Count)
145-
.Select(item => item.Declaration))
139+
var savedParamNames = paramNames;
140+
for (var index = _model.Parameters.Count - 1; index >= 0; index--)
146141
{
147-
var paramIndex = _model.Parameters.FindIndex(item => item.Declaration.Context.GetText() == param.Context.GetText());
148-
if (paramIndex >= paramNames.Count) { return; }
149-
150-
do
142+
var param = _model.Parameters[index];
143+
if (!param.IsRemoved)
151144
{
152-
var paramToRemoveName = paramNames.ElementAt(0).Contains(":=")
153-
? paramNames.Find(item => item.Contains(param.IdentifierName + ":="))
154-
: paramNames.ElementAt(paramIndex);
145+
continue;
146+
}
155147

156-
if (paramToRemoveName == null || !newContent.Contains(paramToRemoveName))
148+
if (param.Name.Contains("ParamArray"))
149+
{
150+
// handle param arrays
151+
while (savedParamNames.Count > index)
157152
{
158-
continue;
153+
savedParamNames.RemoveAt(index);
159154
}
160-
161-
var valueToRemove = paramToRemoveName != paramNames.Last()
162-
? paramToRemoveName + ","
163-
: paramToRemoveName;
164-
165-
var parameterStringIndex = newContent.IndexOf(valueToRemove, currentStringIndex, StringComparison.Ordinal);
166-
if (parameterStringIndex <= -1) { continue; }
167-
168-
newContent = newContent.Remove(parameterStringIndex, valueToRemove.Length);
169-
170-
currentStringIndex = parameterStringIndex;
171-
172-
if (paramToRemoveName == paramNames.Last() && newContent.LastIndexOf(',') != -1)
155+
}
156+
else
157+
{
158+
if (index < savedParamNames.Count && !savedParamNames[index].StripStringLiterals().Contains(":="))
173159
{
174-
newContent = newContent.Remove(newContent.LastIndexOf(','), 1);
160+
savedParamNames.RemoveAt(index);
175161
}
176-
} while (paramIndex >= _model.Parameters.Count - 1 && ++paramIndex < paramNames.Count &&
177-
newContent.Contains(paramNames.ElementAt(paramIndex)));
162+
else
163+
{
164+
var paramIndex = savedParamNames.FindIndex(s => s.StartsWith(param.Declaration.IdentifierName + ":="));
165+
if (paramIndex != -1 && paramIndex < savedParamNames.Count)
166+
{
167+
savedParamNames.RemoveAt(paramIndex);
168+
}
169+
}
170+
}
178171
}
179172

180-
module.ReplaceLine(paramList.Start.Line, newContent);
173+
newContent = newContent.Insert(paramList.Start.Column, string.Join(", ", savedParamNames));
174+
175+
module.ReplaceLine(paramList.Start.Line, newContent.Replace(" _" + Environment.NewLine, string.Empty));
181176
module.DeleteLines(paramList.Start.Line + 1, lineCount - 1);
182177
}
183178

@@ -251,26 +246,6 @@ private string GetOldSignature(Declaration target)
251246
return rewriter.GetText(new Interval(firstTokenIndex, lastTokenIndex));
252247
}
253248

254-
private string ReplaceCommas(string signature, int indexParamRemoved)
255-
{
256-
if (signature.Count(c => c == ',') > indexParamRemoved) { indexParamRemoved++; }
257-
258-
for (int i = 0, commaCounter = 0; i < signature.Length && indexParamRemoved != 0; i++)
259-
{
260-
if (signature.ElementAt(i) == ',')
261-
{
262-
commaCounter++;
263-
}
264-
265-
if (commaCounter == indexParamRemoved)
266-
{
267-
return signature.Remove(i, 1);
268-
}
269-
}
270-
271-
return signature;
272-
}
273-
274249
private void AdjustSignatures()
275250
{
276251
var proc = (dynamic)_model.TargetDeclaration.Context;

RubberduckTests/Refactoring/RemoveParametersTests.cs

Lines changed: 115 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -215,7 +215,7 @@ End Sub
215215
End Sub
216216
217217
Public Sub Goo()
218-
Foo arg2:=""test44"", arg1:=3
218+
Foo arg2:=""test44"", arg1:=3
219219
End Sub
220220
";
221221

@@ -248,6 +248,59 @@ End Sub
248248
Assert.AreEqual(expectedCode, module.Lines());
249249
}
250250

251+
[TestMethod]
252+
public void RemoveParametersRefactoring_CallerArgNameContainsOtherArgName()
253+
{
254+
//Input
255+
const string inputCode =
256+
@"Sub foo(a, b, c)
257+
258+
End Sub
259+
260+
Sub goo()
261+
foo asd, sdf, s
262+
End Sub";
263+
var selection = new Selection(1, 23, 1, 27);
264+
265+
//Expectation
266+
const string expectedCode =
267+
@"Sub foo(a, b)
268+
269+
End Sub
270+
271+
Sub goo()
272+
foo asd, sdf
273+
End Sub";
274+
275+
//Arrange
276+
var builder = new MockVbeBuilder();
277+
VBComponent component;
278+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component, selection);
279+
var module = component.CodeModule;
280+
var mockHost = new Mock<IHostApplication>();
281+
mockHost.SetupAllProperties();
282+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
283+
284+
parser.Parse(new CancellationTokenSource());
285+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
286+
287+
var qualifiedSelection = new QualifiedSelection(new QualifiedModuleName(component), selection);
288+
289+
//Specify Param(s) to remove
290+
var model = new RemoveParametersModel(parser.State, qualifiedSelection, null);
291+
model.Parameters[2].IsRemoved = true;
292+
293+
//SetupFactory
294+
var factory = SetupFactory(model);
295+
296+
//Act
297+
var refactoring = new RemoveParametersRefactoring(vbe.Object, factory.Object);
298+
refactoring.Refactor(qualifiedSelection);
299+
300+
//Assert
301+
Assert.AreEqual(expectedCode, module.Lines());
302+
}
303+
251304
[TestMethod]
252305
public void RemoveParametersRefactoring_RemoveLastFromFunction()
253306
{
@@ -354,7 +407,7 @@ End Sub
354407
End Function
355408
356409
Private Sub Goo(ByVal arg1 As Integer, ByVal arg2 As String)
357-
Foo
410+
Foo
358411
End Sub
359412
";
360413

@@ -406,7 +459,7 @@ Private Sub goo()
406459
End Sub
407460
408461
Private Sub goo()
409-
foo 1, 2, 5, 7
462+
foo 1, 2, 5, 7
410463
End Sub";
411464

412465
//Arrange
@@ -589,7 +642,7 @@ End Sub
589642
End Sub
590643
591644
Private Sub Bar()
592-
Foo ""Hello""
645+
Foo ""Hello""
593646
End Sub
594647
";
595648

@@ -642,9 +695,9 @@ End Sub
642695
End Sub
643696
644697
Private Sub Bar()
645-
Foo 10
698+
Foo 10
646699
End Sub
647-
"; //note: The IDE strips out the extra whitespace, you can't see it but there's a space after "Foo 10 "
700+
";
648701

649702
//Arrange
650703
var builder = new MockVbeBuilder();
@@ -707,9 +760,9 @@ Public Sub Goo(ByVal arg1 As Integer, _
707760
ByVal arg5 As Integer, _
708761
ByVal arg6 As Integer)
709762
710-
Foo ""test""
763+
Foo ""test""
711764
End Sub
712-
"; //note: The IDE strips out the extra whitespace, you can't see it but there are several spaces after " ParamArrayTest ""test"" "
765+
";
713766

714767
//Arrange
715768
var builder = new MockVbeBuilder();
@@ -945,6 +998,59 @@ Private Sub Goo(ByVal arg1 As Integer)
945998
Assert.AreEqual(expectedCode, module.Lines());
946999
}
9471000

1001+
[TestMethod]
1002+
public void RemoveParametersRefactoring_RemoveOptionalParam()
1003+
{
1004+
//Input
1005+
const string inputCode =
1006+
@"Private Sub Foo(ByVal arg1 As Integer, Optional ByVal arg2 As String)
1007+
End Sub
1008+
1009+
Private Sub Goo(ByVal arg1 As Integer)
1010+
Foo arg1
1011+
Foo 1, ""test""
1012+
End Sub";
1013+
var selection = new Selection(1, 23, 1, 27);
1014+
1015+
//Expectation
1016+
const string expectedCode =
1017+
@"Private Sub Foo(ByVal arg1 As Integer)
1018+
End Sub
1019+
1020+
Private Sub Goo(ByVal arg1 As Integer)
1021+
Foo arg1
1022+
Foo 1
1023+
End Sub";
1024+
1025+
//Arrange
1026+
var builder = new MockVbeBuilder();
1027+
VBComponent component;
1028+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component, selection);
1029+
var module = component.CodeModule;
1030+
var mockHost = new Mock<IHostApplication>();
1031+
mockHost.SetupAllProperties();
1032+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
1033+
1034+
parser.Parse(new CancellationTokenSource());
1035+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
1036+
1037+
var qualifiedSelection = new QualifiedSelection(new QualifiedModuleName(component), selection);
1038+
1039+
//Specify Params to remove
1040+
var model = new RemoveParametersModel(parser.State, qualifiedSelection, null);
1041+
model.Parameters[1].IsRemoved = true;
1042+
1043+
//SetupFactory
1044+
var factory = SetupFactory(model);
1045+
1046+
//Act
1047+
var refactoring = new RemoveParametersRefactoring(vbe.Object, factory.Object);
1048+
refactoring.Refactor(qualifiedSelection);
1049+
1050+
//Assert
1051+
Assert.AreEqual(expectedCode, module.Lines());
1052+
}
1053+
9481054
[TestMethod]
9491055
public void RemoveParametersRefactoring_SignatureOnMultipleLines()
9501056
{
@@ -1150,7 +1256,7 @@ End Sub
11501256
11511257
Private Sub Goo(ByVal arg1 as Integer, ByVal arg2 As String, ByVal arg3 As Date)
11521258
1153-
Foo arg2, arg3
1259+
Foo arg2, arg3
11541260
11551261
End Sub
11561262
"; // note: IDE removes excess spaces

0 commit comments

Comments
 (0)