Skip to content

Commit b7ca91a

Browse files
committed
Merge pull request #914 from Hosch250/ProcuedureShouldBeFunction
Procuedure should be function
2 parents 861357e + b9761a6 commit b7ca91a

File tree

7 files changed

+236
-2
lines changed

7 files changed

+236
-2
lines changed

RetailCoder.VBE/Inspections/InspectionsUI.Designer.cs

Lines changed: 37 additions & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

RetailCoder.VBE/Inspections/InspectionsUI.resx

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -267,11 +267,18 @@
267267
<data name="UntypedFunctionUsageInspectionName" xml:space="preserve">
268268
<value>Use of variant-returning string function</value>
269269
</data>
270+
<data name="ProcedureShouldBeFunctionInspection" xml:space="preserve">
271+
<value>Procedure '{0}' should be a function.</value>
272+
<comment>{0} Procedure name</comment>
273+
</data>
274+
<data name="ProcedureShouldBeFunctionInspectionQuickFix" xml:space="preserve">
275+
<value>Replace procedure with function and update usages.</value>
276+
</data>
270277
<data name="UseMeaningfulNameInspection" xml:space="preserve">
271278
<value>Consider renaming {0} '{1}'</value>
272279
</data>
273280
<data name="UseMeaningfulNameInspectionMeta" xml:space="preserve">
274-
<value>Identifier names should indicate what they're used for, and should be readable; avoid disemvoweling, numeric suffixes and 1-2 character names.</value>
281+
<value>Identifier names should indicate what they're used for and should be readable; avoid disemvoweling, numeric suffixes, and 1-2 character names.</value>
275282
</data>
276283
<data name="UseMeaningfulNameInspectionName" xml:space="preserve">
277284
<value>Use meaningful names</value>
@@ -300,4 +307,10 @@
300307
<data name="WriteOnlyPropertyInspectionName" xml:space="preserve">
301308
<value>Write-only property</value>
302309
</data>
310+
<data name="ProcedureShouldBeFunctionInspectionMeta" xml:space="preserve">
311+
<value>A procedure has one ByRef parameter. Consider creating a function that returns the value instead.</value>
312+
</data>
313+
<data name="ProcedureShouldBeFunctionInspectionName" xml:space="preserve">
314+
<value>Convert procedure to function</value>
315+
</data>
303316
</root>
Lines changed: 34 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,34 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Parsing;
4+
using Rubberduck.Parsing.Grammar;
5+
using Rubberduck.Parsing.VBA;
6+
7+
namespace Rubberduck.Inspections
8+
{
9+
public class ProcedureShouldBeFunctionInspection : IInspection
10+
{
11+
public ProcedureShouldBeFunctionInspection()
12+
{
13+
Severity = CodeInspectionSeverity.Warning;
14+
}
15+
16+
public string Name { get { return "ProcedureShouldBeFunctionInspection"; } }
17+
public string Meta { get { return InspectionsUI.ResourceManager.GetString(Name + "Meta"); } }
18+
public string Description { get { return InspectionsUI.ProcedureShouldBeFunctionInspection; } }
19+
public CodeInspectionType InspectionType { get { return CodeInspectionType.LanguageOpportunities; } }
20+
public CodeInspectionSeverity Severity { get; set; }
21+
22+
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
23+
{
24+
return state.ArgListsWithOneByRefParam
25+
.Where(context => context.Context.Parent is VBAParser.SubStmtContext)
26+
.Select(context => new ProcedureShouldBeFunctionInspectionResult(this,
27+
state,
28+
new QualifiedContext<VBAParser.ArgListContext>(context.ModuleName,
29+
context.Context as VBAParser.ArgListContext),
30+
new QualifiedContext<VBAParser.SubStmtContext>(context.ModuleName,
31+
context.Context.Parent as VBAParser.SubStmtContext)));
32+
}
33+
}
34+
}
Lines changed: 121 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,121 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using Rubberduck.Parsing;
5+
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.Parsing.VBA;
7+
using Rubberduck.VBEditor;
8+
9+
namespace Rubberduck.Inspections
10+
{
11+
public class ProcedureShouldBeFunctionInspectionResult : CodeInspectionResultBase
12+
{
13+
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;
14+
15+
public ProcedureShouldBeFunctionInspectionResult(IInspection inspection, RubberduckParserState state, QualifiedContext<VBAParser.ArgListContext> argListQualifiedContext, QualifiedContext<VBAParser.SubStmtContext> subStmtQualifiedContext)
16+
: base(inspection,
17+
string.Format(inspection.Description, subStmtQualifiedContext.Context.ambiguousIdentifier().GetText()),
18+
subStmtQualifiedContext.ModuleName,
19+
subStmtQualifiedContext.Context.ambiguousIdentifier())
20+
{
21+
_quickFixes = new[]
22+
{
23+
new ChangeProcedureToFunction(state, argListQualifiedContext, subStmtQualifiedContext, QualifiedSelection),
24+
};
25+
}
26+
27+
public override IEnumerable<CodeInspectionQuickFix> QuickFixes { get { return _quickFixes; } }
28+
}
29+
30+
public class ChangeProcedureToFunction : CodeInspectionQuickFix
31+
{
32+
private readonly RubberduckParserState _state;
33+
private readonly QualifiedContext<VBAParser.ArgListContext> _argListQualifiedContext;
34+
private readonly QualifiedContext<VBAParser.SubStmtContext> _subStmtQualifiedContext;
35+
private readonly QualifiedContext<VBAParser.ArgContext> _argQualifiedContext;
36+
37+
public ChangeProcedureToFunction(RubberduckParserState state,
38+
QualifiedContext<VBAParser.ArgListContext> argListQualifiedContext,
39+
QualifiedContext<VBAParser.SubStmtContext> subStmtQualifiedContext,
40+
QualifiedSelection selection)
41+
: base(subStmtQualifiedContext.Context, selection, InspectionsUI.ProcedureShouldBeFunctionInspectionQuickFix)
42+
{
43+
_state = state;
44+
_argListQualifiedContext = argListQualifiedContext;
45+
_subStmtQualifiedContext = subStmtQualifiedContext;
46+
_argQualifiedContext = new QualifiedContext<VBAParser.ArgContext>(_argListQualifiedContext.ModuleName,
47+
_argListQualifiedContext.Context.arg()
48+
.First(a => a.BYREF() != null || (a.BYREF() == null && a.BYVAL() == null)));
49+
}
50+
51+
public override void Fix()
52+
{
53+
UpdateSignature();
54+
UpdateCalls();
55+
}
56+
57+
private void UpdateSignature()
58+
{
59+
var argListText = _argListQualifiedContext.Context.GetText();
60+
var subStmtText = _subStmtQualifiedContext.Context.GetText();
61+
var argText = _argQualifiedContext.Context.GetText();
62+
63+
var newArgText = argText.Contains("ByRef ") ? argText.Replace("ByRef ", "ByVal ") : "ByVal " + argText;
64+
65+
var newFunctionWithoutReturn = subStmtText.Insert(subStmtText.IndexOf(argListText, StringComparison.Ordinal) + argListText.Length,
66+
_argQualifiedContext.Context.asTypeClause().GetText())
67+
.Replace("Sub", "Function")
68+
.Replace(argText, newArgText);
69+
70+
var newfunctionWithReturn = newFunctionWithoutReturn
71+
.Insert(newFunctionWithoutReturn.LastIndexOf(Environment.NewLine, StringComparison.Ordinal),
72+
" " + _subStmtQualifiedContext.Context.ambiguousIdentifier().GetText() +
73+
" = " + _argQualifiedContext.Context.ambiguousIdentifier().GetText());
74+
75+
var rewriter = _state.GetRewriter(_subStmtQualifiedContext.ModuleName.Component);
76+
rewriter.Replace(_subStmtQualifiedContext.Context.Start, newfunctionWithReturn);
77+
78+
var module = _argListQualifiedContext.ModuleName.Component.CodeModule;
79+
80+
module.DeleteLines(_subStmtQualifiedContext.Context.Start.Line,
81+
_subStmtQualifiedContext.Context.Stop.Line - _subStmtQualifiedContext.Context.Start.Line + 1);
82+
module.InsertLines(_subStmtQualifiedContext.Context.Start.Line, newfunctionWithReturn);
83+
}
84+
85+
private void UpdateCalls()
86+
{
87+
var procedureName = _subStmtQualifiedContext.Context.ambiguousIdentifier().GetText();
88+
89+
var procedure =
90+
_state.AllDeclarations.SingleOrDefault(d =>
91+
!d.IsBuiltIn &&
92+
d.IdentifierName == procedureName &&
93+
d.Context is VBAParser.SubStmtContext &&
94+
d.ComponentName == _subStmtQualifiedContext.ModuleName.ComponentName &&
95+
d.Project == _subStmtQualifiedContext.ModuleName.Project);
96+
97+
if (procedure == null) { return; }
98+
99+
foreach (var reference in procedure.References.OrderByDescending(o => o.Selection.StartLine).ThenByDescending(d => d.Selection.StartColumn))
100+
{
101+
var module = reference.QualifiedModuleName.Component.CodeModule;
102+
103+
var referenceParent = reference.Context.Parent as VBAParser.ICS_B_ProcedureCallContext;
104+
if (referenceParent == null) { continue; }
105+
106+
var referenceText = reference.Context.Parent.GetText();
107+
var newCall = referenceParent.argsCall().argCall().ToList().ElementAt(_argListQualifiedContext.Context.arg().ToList().IndexOf(_argQualifiedContext.Context)).GetText() +
108+
" = " + _subStmtQualifiedContext.Context.ambiguousIdentifier().GetText() +
109+
"(" + referenceParent.argsCall().GetText() + ")";
110+
111+
var oldLines = module.Lines[reference.Selection.StartLine, reference.Selection.LineCount];
112+
113+
var newText = oldLines.Remove(reference.Selection.StartColumn - 1, referenceText.Length)
114+
.Insert(reference.Selection.StartColumn - 1, newCall);
115+
116+
module.DeleteLines(reference.Selection.StartLine, reference.Selection.LineCount);
117+
module.InsertLines(reference.Selection.StartLine, newText);
118+
}
119+
}
120+
}
121+
}

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -304,6 +304,8 @@
304304
<DesignTime>True</DesignTime>
305305
<DependentUpon>InspectionsUI.resx</DependentUpon>
306306
</Compile>
307+
<Compile Include="Inspections\ProcedureShouldBeFunctionInspection.cs" />
308+
<Compile Include="Inspections\ProcedureShouldBeFunctionInspectionResult.cs" />
307309
<Compile Include="Inspections\UntypedFunctionUsageInspectionResult.cs" />
308310
<Compile Include="Inspections\UseMeaningfulNameInspection.cs" />
309311
<Compile Include="Inspections\UseMeaningfulNameInspectionResult.cs" />

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -187,12 +187,14 @@ private void ParseInternal(VBComponent vbComponent, CancellationToken token)
187187
var obsoleteCallsListener = new ObsoleteCallStatementListener();
188188
var obsoleteLetListener = new ObsoleteLetStatementListener();
189189
var emptyStringLiteralListener = new EmptyStringLiteralListener();
190+
var argListsWithOneByRefParam = new ArgListWithOneByRefParamListener();
190191

191192
var listeners = new IParseTreeListener[]
192193
{
193194
obsoleteCallsListener,
194195
obsoleteLetListener,
195196
emptyStringLiteralListener,
197+
argListsWithOneByRefParam,
196198
};
197199

198200
token.ThrowIfCancellationRequested();
@@ -222,6 +224,7 @@ private void ParseInternal(VBComponent vbComponent, CancellationToken token)
222224
_state.ObsoleteCallContexts = obsoleteCallsListener.Contexts.Select(context => new QualifiedContext(qualifiedName, context));
223225
_state.ObsoleteLetContexts = obsoleteLetListener.Contexts.Select(context => new QualifiedContext(qualifiedName, context));
224226
_state.EmptyStringLiterals = emptyStringLiteralListener.Contexts.Select(context => new QualifiedContext(qualifiedName, context));
227+
_state.ArgListsWithOneByRefParam = argListsWithOneByRefParam.Contexts.Select(context => new QualifiedContext(qualifiedName, context));
225228

226229
State.SetModuleState(vbComponent, ParserState.Parsed);
227230
}
@@ -324,5 +327,19 @@ public override void ExitLiteral(VBAParser.LiteralContext context)
324327
}
325328
}
326329
}
330+
331+
private class ArgListWithOneByRefParamListener : VBABaseListener
332+
{
333+
private readonly IList<VBAParser.ArgListContext> _contexts = new List<VBAParser.ArgListContext>();
334+
public IEnumerable<VBAParser.ArgListContext> Contexts { get { return _contexts; } }
335+
336+
public override void ExitArgList(VBAParser.ArgListContext context)
337+
{
338+
if (context.arg() != null && context.arg().Count(a => a.BYREF() != null || (a.BYREF() == null && a.BYVAL() == null)) == 1)
339+
{
340+
_contexts.Add(context);
341+
}
342+
}
343+
}
327344
}
328345
}

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -155,6 +155,17 @@ public IEnumerable<QualifiedContext> EmptyStringLiterals
155155
internal set { _emptyStringLiterals = value; }
156156
}
157157

158+
private IEnumerable<QualifiedContext> _argListsWithOneByRefParam = new List<QualifiedContext>();
159+
160+
/// <summary>
161+
/// Gets <see cref="ParserRuleContext"/> objects representing 'Call' statements in the parse tree.
162+
/// </summary>
163+
public IEnumerable<QualifiedContext> ArgListsWithOneByRefParam
164+
{
165+
get { return _argListsWithOneByRefParam; }
166+
internal set { _argListsWithOneByRefParam = value; }
167+
}
168+
158169
private readonly ConcurrentDictionary<VBComponent, IEnumerable<CommentNode>> _comments =
159170
new ConcurrentDictionary<VBComponent, IEnumerable<CommentNode>>();
160171

0 commit comments

Comments
 (0)