Skip to content

Commit ae2b8d0

Browse files
committed
2 parents 1558812 + 8632df5 commit ae2b8d0

File tree

4 files changed

+204
-23
lines changed

4 files changed

+204
-23
lines changed
Lines changed: 61 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,11 @@
11
using Antlr4.Runtime;
2+
using Antlr4.Runtime.Tree;
23
using Rubberduck.Inspections.Abstract;
34
using Rubberduck.Inspections.Resources;
45
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.Parsing.Symbols;
57
using Rubberduck.VBEditor;
6-
using System.Text.RegularExpressions;
8+
using System.Linq;
79

810
namespace Rubberduck.Inspections.QuickFixes
911
{
@@ -12,31 +14,75 @@ namespace Rubberduck.Inspections.QuickFixes
1214
/// </summary>
1315
public class PassParameterByReferenceQuickFix : QuickFixBase
1416
{
15-
public PassParameterByReferenceQuickFix(ParserRuleContext context, QualifiedSelection selection)
16-
: base(context, selection, InspectionsUI.PassParameterByReferenceQuickFix)
17+
private Declaration _target;
18+
19+
public PassParameterByReferenceQuickFix(Declaration target, QualifiedSelection selection)
20+
: base(target.Context, selection, InspectionsUI.PassParameterByReferenceQuickFix)
1721
{
22+
_target = target;
1823
}
1924

2025
public override void Fix()
2126
{
22-
var parameter = Context.GetText();
27+
var argCtxt = GetArgContextForIdentifier(Context.Parent.Parent, _target.IdentifierName);
2328

24-
var parts = parameter.Split(new char[]{' '},2);
25-
if (1 != parts.GetUpperBound(0))
26-
{
27-
return;
28-
}
29-
parts[0] = parts[0].Replace(Tokens.ByVal, Tokens.ByRef);
30-
var newContent = parts[0] + " " + parts[1];
29+
var terminalNode = argCtxt.BYVAL();
3130

32-
var selection = Selection.Selection;
31+
var replacementLine = GenerateByRefReplacementLine(terminalNode);
32+
33+
ReplaceModuleLine(terminalNode.Symbol.Line, replacementLine);
34+
35+
}
36+
private VBAParser.ArgContext GetArgContextForIdentifier(RuleContext context, string identifier)
37+
{
38+
var argList = GetArgListForContext(context);
39+
return argList.arg().SingleOrDefault(parameter =>
40+
Identifier.GetName(parameter).Equals(identifier));
41+
}
42+
private string GenerateByRefReplacementLine(ITerminalNode terminalNode)
43+
{
44+
var module = Selection.QualifiedName.Component.CodeModule;
45+
var byValTokenLine = module.GetLines(terminalNode.Symbol.Line, 1);
3346

47+
return ReplaceAtIndex(byValTokenLine, Tokens.ByVal, Tokens.ByRef, terminalNode.Symbol.Column);
48+
}
49+
private void ReplaceModuleLine(int lineNumber, string replacementLine)
50+
{
3451
var module = Selection.QualifiedName.Component.CodeModule;
52+
module.DeleteLines(lineNumber);
53+
module.InsertLines(lineNumber, replacementLine);
54+
}
55+
private string ReplaceAtIndex(string input, string toReplace, string replacement, int startIndex)
56+
{
57+
int stopIndex = startIndex + toReplace.Length;
58+
var prefix = input.Substring(0, startIndex);
59+
var suffix = input.Substring(stopIndex + 1);
60+
var tokenToBeReplaced = input.Substring(startIndex, stopIndex - startIndex + 1);
61+
return prefix + tokenToBeReplaced.Replace(toReplace, replacement) + suffix;
62+
}
63+
private VBAParser.ArgListContext GetArgListForContext(RuleContext context)
64+
{
65+
if (context is VBAParser.SubStmtContext)
66+
{
67+
return ((VBAParser.SubStmtContext)context).argList();
68+
}
69+
else if (context is VBAParser.FunctionStmtContext)
70+
{
71+
return ((VBAParser.FunctionStmtContext)context).argList();
72+
}
73+
else if (context is VBAParser.PropertyLetStmtContext)
74+
{
75+
return ((VBAParser.PropertyLetStmtContext)context).argList();
76+
}
77+
else if (context is VBAParser.PropertyGetStmtContext)
78+
{
79+
return ((VBAParser.PropertyGetStmtContext)context).argList();
80+
}
81+
else if (context is VBAParser.PropertySetStmtContext)
3582
{
36-
var lines = module.GetLines(selection.StartLine, selection.LineCount);
37-
var result = lines.Replace(parameter, newContent);
38-
module.ReplaceLine(selection.StartLine, result);
83+
return ((VBAParser.PropertySetStmtContext)context).argList();
3984
}
85+
return null;
4086
}
4187
}
4288
}

RetailCoder.VBE/Inspections/Results/AssignedByValParameterInspectionResult.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ public override IEnumerable<QuickFixBase> QuickFixes
2828
return _quickFixes ?? (_quickFixes = new QuickFixBase[]
2929
{
3030
new AssignedByValParameterQuickFix(Target, QualifiedSelection),
31-
new PassParameterByReferenceQuickFix(Target.Context, QualifiedSelection),
31+
new PassParameterByReferenceQuickFix(Target, QualifiedSelection),
3232
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName)
3333
});
3434
}

Rubberduck.Parsing/Symbols/Identifier.cs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,11 @@ namespace Rubberduck.Parsing.Symbols
77
{
88
public static class Identifier
99
{
10+
public static string GetName(VBAParser.ArgContext context)
11+
{
12+
return GetName(context.unrestrictedIdentifier());
13+
}
14+
1015
public static string GetName(VBAParser.FunctionNameContext context)
1116
{
1217
return GetName(context.identifier());

RubberduckTests/Inspections/AssignedByValParameterInspectionTests.cs

Lines changed: 137 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -97,19 +97,152 @@ Dim var1 As Integer
9797
[TestCategory("Inspections")]
9898
public void AssignedByValParameter_QuickFixWorks()
9999
{
100-
const string inputCode =
101-
@"Public Sub Foo(ByVal barByVal As String)
100+
101+
string inputCode =
102+
@"Public Sub Foo(Optional ByVal barByVal As String = ""XYZ"")
102103
Let barByVal = ""test""
103104
End Sub";
104-
const string expectedCode =
105-
@"Public Sub Foo(ByRef barByVal As String)
105+
string expectedCode =
106+
@"Public Sub Foo(Optional ByRef barByVal As String = ""XYZ"")
106107
Let barByVal = ""test""
107108
End Sub";
108109

109110
var quickFixResult = ApplyPassParameterByReferenceQuickFixToVBAFragment(inputCode);
110111
Assert.AreEqual(expectedCode, quickFixResult);
112+
113+
//check when ByVal argument is one of several parameters
114+
inputCode =
115+
@"Public Sub Foo(ByRef firstArg As Long, Optional ByVal barByVal As String = """", secondArg as Double)
116+
Let barByVal = ""test""
117+
End Sub";
118+
expectedCode =
119+
@"Public Sub Foo(ByRef firstArg As Long, Optional ByRef barByVal As String = """", secondArg as Double)
120+
Let barByVal = ""test""
121+
End Sub";
122+
123+
quickFixResult = ApplyPassParameterByReferenceQuickFixToVBAFragment(inputCode);
124+
Assert.AreEqual(expectedCode, quickFixResult);
125+
126+
inputCode =
127+
@"
128+
Private Sub Foo(Optional ByVal _
129+
bar _
130+
As _
131+
Long = 4, _
132+
ByVal _
133+
barTwo _
134+
As _
135+
Long)
136+
bar = 42
137+
End Sub
138+
"
139+
;
140+
expectedCode =
141+
@"
142+
Private Sub Foo(Optional ByRef _
143+
bar _
144+
As _
145+
Long = 4, _
146+
ByVal _
147+
barTwo _
148+
As _
149+
Long)
150+
bar = 42
151+
End Sub
152+
"
153+
;
154+
quickFixResult = ApplyPassParameterByReferenceQuickFixToVBAFragment(inputCode);
155+
Assert.AreEqual(expectedCode, quickFixResult);
156+
157+
inputCode =
158+
@"Private Sub Foo(ByVal barByVal As Long, ByVal _xByValbar As Long, ByVal _
159+
barTwo _
160+
As _
161+
Long)
162+
barTwo = 42
163+
End Sub
164+
";
165+
expectedCode =
166+
@"Private Sub Foo(ByVal barByVal As Long, ByVal _xByValbar As Long, ByRef _
167+
barTwo _
168+
As _
169+
Long)
170+
barTwo = 42
171+
End Sub
172+
";
173+
174+
quickFixResult = ApplyPassParameterByReferenceQuickFixToVBAFragment(inputCode);
175+
Assert.AreEqual(expectedCode, quickFixResult);
176+
177+
inputCode =
178+
@"Private Sub Foo(ByVal barByVal As Long, ByVal barTwoon As Long, ByVal _
179+
barTwo _
180+
As _
181+
Long)
182+
barTwo = 42
183+
End Sub
184+
";
185+
expectedCode =
186+
@"Private Sub Foo(ByVal barByVal As Long, ByVal barTwoon As Long, ByRef _
187+
barTwo _
188+
As _
189+
Long)
190+
barTwo = 42
191+
End Sub
192+
";
193+
194+
quickFixResult = ApplyPassParameterByReferenceQuickFixToVBAFragment(inputCode);
195+
Assert.AreEqual(expectedCode, quickFixResult);
196+
197+
inputCode =
198+
@"Private Sub Foo(ByVal barByVal As Long, ByVal barTwoon As Long, ByVal barTwo _
199+
As _
200+
Long)
201+
barTwo = 42
202+
End Sub
203+
";
204+
expectedCode =
205+
@"Private Sub Foo(ByVal barByVal As Long, ByVal barTwoon As Long, ByRef barTwo _
206+
As _
207+
Long)
208+
barTwo = 42
209+
End Sub
210+
";
211+
212+
quickFixResult = ApplyPassParameterByReferenceQuickFixToVBAFragment(inputCode);
213+
Assert.AreEqual(expectedCode, quickFixResult);
214+
215+
inputCode =
216+
@"Sub DoSomething(_
217+
ByVal foo As Long, _
218+
ByRef _
219+
bar, _
220+
ByRef barbecue _
221+
)
222+
foo = 4
223+
bar = barbecue * _
224+
bar + foo / barbecue
225+
End Sub
226+
";
227+
228+
expectedCode =
229+
@"Sub DoSomething(_
230+
ByRef foo As Long, _
231+
ByRef _
232+
bar, _
233+
ByRef barbecue _
234+
)
235+
foo = 4
236+
bar = barbecue * _
237+
bar + foo / barbecue
238+
End Sub
239+
";
240+
quickFixResult = ApplyPassParameterByReferenceQuickFixToVBAFragment(inputCode);
241+
Assert.AreEqual(expectedCode, quickFixResult);
242+
111243
}
112244

245+
113246
[TestMethod]
114247
[TestCategory("Inspections")]
115248
public void AssignedByValParameter_IgnoreQuickFixWorks()
@@ -507,9 +640,6 @@ private Mock<IVBE> BuildMockVBEStandardModuleForVBAFragment(string inputCode)
507640
{
508641
var builder = new MockVbeBuilder();
509642
IVBComponent component;
510-
//TODO: removal of the two lines below have no effect on the outcome of any test...remove?
511-
//var mockHost = new Mock<IHostApplication>();
512-
//mockHost.SetupAllProperties();
513643
return builder.BuildFromSingleStandardModule(inputCode, out component);
514644

515645
}

0 commit comments

Comments
 (0)