Skip to content

Commit 6cf1536

Browse files
committed
Replace Exit Sub when converting Subs to Functions
This assigns the return value and then exists the function instead of exiting the procedure that gets converted. These two statements are inserted separated by a statement separator instead of doing it on multiple lines to avoid having a separate code path if the Exit Sub is in a single line if statement.
1 parent 877d0f6 commit 6cf1536

File tree

2 files changed

+141
-4
lines changed

2 files changed

+141
-4
lines changed

Rubberduck.CodeAnalysis/QuickFixes/Concrete/ChangeProcedureToFunctionQuickFix.cs

Lines changed: 27 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -59,23 +59,31 @@ public override void Fix(IInspectionResult result, IRewriteSession rewriteSessio
5959
var arg = parameterizedDeclaration.Parameters.First(p => p.IsByRef || p.IsImplicitByRef);
6060
var argIndex = parameterizedDeclaration.Parameters.IndexOf(arg);
6161

62-
UpdateSignature(result.Target, arg, rewriteSession);
62+
UpdateProcedure(result.Target, arg, rewriteSession);
6363
foreach (var reference in result.Target.References.Where(reference => !reference.IsDefaultMemberAccess))
6464
{
6565
UpdateCall(reference, argIndex, rewriteSession);
6666
}
6767
}
6868

69-
private void UpdateSignature(Declaration target, ParameterDeclaration arg, IRewriteSession rewriteSession)
69+
private void UpdateProcedure(Declaration target, ParameterDeclaration arg, IRewriteSession rewriteSession)
7070
{
7171
var subStmt = (VBAParser.SubStmtContext) target.Context;
7272
var argContext = (VBAParser.ArgContext)arg.Context;
73-
73+
var argName = argContext.unrestrictedIdentifier().GetText();
7474
var rewriter = rewriteSession.CheckOutModuleRewriter(target.QualifiedModuleName);
7575

76+
UpdateSignature(subStmt, arg, rewriter);
77+
AddReturnStatement(subStmt, argName, rewriter);
78+
ReplaceExitSubs(subStmt, argName, rewriter);
79+
}
80+
81+
private void UpdateSignature(VBAParser.SubStmtContext subStmt, ParameterDeclaration arg, IModuleRewriter rewriter)
82+
{
7683
rewriter.Replace(subStmt.SUB(), Tokens.Function);
7784
rewriter.Replace(subStmt.END_SUB(), "End Function");
7885

86+
var argContext = (VBAParser.ArgContext)arg.Context;
7987
rewriter.InsertAfter(subStmt.argList().Stop.TokenIndex, $" As {arg.AsTypeName}");
8088

8189
if (arg.IsByRef)
@@ -86,11 +94,26 @@ private void UpdateSignature(Declaration target, ParameterDeclaration arg, IRewr
8694
{
8795
rewriter.InsertBefore(argContext.unrestrictedIdentifier().Start.TokenIndex, Tokens.ByVal);
8896
}
97+
}
8998

90-
var returnStmt = $" {subStmt.subroutineName().GetText()} = {argContext.unrestrictedIdentifier().GetText()}{Environment.NewLine}";
99+
private void AddReturnStatement(VBAParser.SubStmtContext subStmt, string argName, IModuleRewriter rewriter)
100+
{
101+
var returnStmt = $" {subStmt.subroutineName().GetText()} = {argName}{Environment.NewLine}";
102+
// This exploits that the VBE will realign the End Function statement automatically.
91103
rewriter.InsertBefore(subStmt.END_SUB().Symbol.TokenIndex, returnStmt);
92104
}
93105

106+
private void ReplaceExitSubs(VBAParser.SubStmtContext subStmt, string argName, IModuleRewriter rewriter)
107+
{
108+
// We use a statement separator here to be able to deal with single line if statments without too much issues.
109+
var exitFunctionCode = $"{subStmt.subroutineName().GetText()} = {argName}: Exit Function";
110+
foreach (var exitSub in subStmt.GetDescendents<VBAParser.ExitStmtContext>())
111+
{
112+
rewriter.Replace(exitSub, exitFunctionCode);
113+
}
114+
}
115+
116+
94117
private void UpdateCall(IdentifierReference reference, int argIndex, IRewriteSession rewriteSession)
95118
{
96119
var rewriter = rewriteSession.CheckOutModuleRewriter(reference.QualifiedModuleName);

RubberduckTests/QuickFixes/ChangeProcedureToFunctionQuickFixTests.cs

Lines changed: 114 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -192,6 +192,120 @@ Foo fizz
192192
Foo = arg1
193193
End Function
194194
195+
Sub Goo(ByVal a As Integer)
196+
Dim fizz As Integer
197+
fizz = Foo(fizz)
198+
End Sub";
199+
200+
var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new ProcedureCanBeWrittenAsFunctionInspection(state));
201+
Assert.AreEqual(expectedCode, actualCode);
202+
}
203+
204+
// Based on issue #6139 at https://github.com/rubberduck-vba/Rubberduck/issues/6139
205+
[Test]
206+
[Category("QuickFixes")]
207+
public void ProcedureShouldBeFunction_QuickFixWorks_ExitSub()
208+
{
209+
const string inputCode =
210+
@"Private Sub Foo(ByRef arg1 As Integer)
211+
If condition Then
212+
Exit Sub
213+
End If
214+
215+
arg1 = 42
216+
End Sub
217+
218+
Sub Goo(ByVal a As Integer)
219+
Dim fizz As Integer
220+
Foo fizz
221+
End Sub";
222+
223+
const string expectedCode =
224+
@"Private Function Foo(ByVal arg1 As Integer) As Integer
225+
If condition Then
226+
Foo = arg1: Exit Function
227+
End If
228+
229+
arg1 = 42
230+
Foo = arg1
231+
End Function
232+
233+
Sub Goo(ByVal a As Integer)
234+
Dim fizz As Integer
235+
fizz = Foo(fizz)
236+
End Sub";
237+
238+
var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new ProcedureCanBeWrittenAsFunctionInspection(state));
239+
Assert.AreEqual(expectedCode, actualCode);
240+
}
241+
242+
[Test]
243+
[Category("QuickFixes")]
244+
public void ProcedureShouldBeFunction_QuickFixWorks_ExitSubIndentationRespected()
245+
{
246+
const string inputCode =
247+
@"Private Sub Foo(ByRef arg1 As Integer)
248+
If condition Then
249+
If otherCondition Then
250+
Exit Sub
251+
End If
252+
End If
253+
254+
arg1 = 42
255+
End Sub
256+
257+
Sub Goo(ByVal a As Integer)
258+
Dim fizz As Integer
259+
Foo fizz
260+
End Sub";
261+
262+
const string expectedCode =
263+
@"Private Function Foo(ByVal arg1 As Integer) As Integer
264+
If condition Then
265+
If otherCondition Then
266+
Foo = arg1: Exit Function
267+
End If
268+
End If
269+
270+
arg1 = 42
271+
Foo = arg1
272+
End Function
273+
274+
Sub Goo(ByVal a As Integer)
275+
Dim fizz As Integer
276+
fizz = Foo(fizz)
277+
End Sub";
278+
279+
var actualCode = ApplyQuickFixToFirstInspectionResult(inputCode, state => new ProcedureCanBeWrittenAsFunctionInspection(state));
280+
Assert.AreEqual(expectedCode, actualCode);
281+
}
282+
283+
[Test]
284+
[Category("QuickFixes")]
285+
public void ProcedureShouldBeFunction_QuickFixWorks_ExitSub_InSingleLineIf()
286+
{
287+
const string inputCode =
288+
@"Private Sub Foo(ByRef arg1 As Integer)
289+
If condition Then Exit Sub
290+
If otherContirion Then: Else Exit Sub
291+
292+
arg1 = 42
293+
End Sub
294+
295+
Sub Goo(ByVal a As Integer)
296+
Dim fizz As Integer
297+
Foo fizz
298+
End Sub";
299+
300+
const string expectedCode =
301+
@"Private Function Foo(ByVal arg1 As Integer) As Integer
302+
If condition Then Foo = arg1: Exit Function
303+
If otherContirion Then: Else Foo = arg1: Exit Function
304+
305+
arg1 = 42
306+
Foo = arg1
307+
End Function
308+
195309
Sub Goo(ByVal a As Integer)
196310
Dim fizz As Integer
197311
fizz = Foo(fizz)

0 commit comments

Comments
 (0)