Skip to content

Commit 728a8e4

Browse files
committed
Merge branch 'next' of https://github.com/BZngr/Rubberduck into next
2 parents 0c76eea + 4c2e530 commit 728a8e4

19 files changed

+282
-77
lines changed

RetailCoder.VBE/Inspections/Concrete/Inspector.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -139,7 +139,7 @@ before moving them into the ParseTreeResults after qualifying them
139139

140140
if (argListWithOneByRefParamListener != null)
141141
{
142-
result.AddRange(argListWithOneByRefParamListener.Contexts.Select(context => new QualifiedContext<VBAParser.ArgListContext>(componentTreePair.Key, context)));
142+
result.AddRange(argListWithOneByRefParamListener.Contexts.Select(context => new QualifiedContext<VBAParser.SubstmtContext>(componentTreePair.Key, context)));
143143
}
144144
if (emptyStringLiteralListener != null)
145145
{

RetailCoder.VBE/Inspections/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ public ProcedureCanBeWrittenAsFunctionInspection(RubberduckParserState state)
2727
public override string Description { get { return InspectionsUI.ProcedureCanBeWrittenAsFunctionInspectionName; } }
2828
public override CodeInspectionType InspectionType { get { return CodeInspectionType.LanguageOpportunities; } }
2929

30-
public IEnumerable<QualifiedContext<VBAParser.ArgListContext>> ParseTreeResults { get { return _results.OfType<QualifiedContext<VBAParser.ArgListContext>>(); } }
30+
public IEnumerable<QualifiedContext<VBAParser.SubstmtContext>> ParseTreeResults { get { return _results.OfType<QualifiedContext<VBAParser.SubstmtContext>>(); } }
3131

3232
public void SetResults(IEnumerable<QualifiedContext> results)
3333
{
@@ -62,17 +62,17 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
6262
.Select(result => new ProcedureCanBeWrittenAsFunctionInspectionResult(
6363
this,
6464
State,
65-
new QualifiedContext<VBAParser.ArgListContext>(result.QualifiedName,result.Context.GetChild<VBAParser.ArgListContext>(0)),
65+
new QualifiedContext<VBAParser.SubstmtContext>(result.QualifiedName,result.Context.GetChild<VBAParser.SubstmtContext>(0)),
6666
new QualifiedContext<VBAParser.SubStmtContext>(result.QualifiedName, (VBAParser.SubStmtContext)result.Context))
6767
);
6868
}
6969

7070
public class SingleByRefParamArgListListener : VBAParserBaseListener
7171
{
72-
private readonly IList<VBAParser.ArgListContext> _contexts = new List<VBAParser.ArgListContext>();
73-
public IEnumerable<VBAParser.ArgListContext> Contexts { get { return _contexts; } }
72+
private readonly IList<VBAParser.SubstmtContext> _contexts = new List<VBAParser.SubstmtContext>();
73+
public IEnumerable<VBAParser.SubstmtContext> Contexts { get { return _contexts; } }
7474

75-
public override void ExitArgList(VBAParser.ArgListContext context)
75+
public override void ExitArgList(VBAParser.SubstmtContext context)
7676
{
7777
var args = context.arg();
7878
if (args != null && args.All(a => a.PARAMARRAY() == null && a.LPAREN() == null) && args.Count(a => a.BYREF() != null || (a.BYREF() == null && a.BYVAL() == null)) == 1)

RetailCoder.VBE/Inspections/QuickFixes/DeclareAsExplicitVariantQuickFix.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -68,9 +68,9 @@ private string DeclareExplicitVariant(VBAParser.ArgContext context, out string i
6868
var fix = string.Empty;
6969
foreach (var child in memberContext.children)
7070
{
71-
if (child is VBAParser.ArgListContext)
71+
if (child is VBAParser.SubstmtContext)
7272
{
73-
foreach (var tree in ((VBAParser.ArgListContext) child).children)
73+
foreach (var tree in ((VBAParser.SubstmtContext) child).children)
7474
{
7575
if (tree.Equals(context))
7676
{
Lines changed: 91 additions & 16 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 static Rubberduck.Parsing.Grammar.VBAParser;
79

810
namespace Rubberduck.Inspections.QuickFixes
911
{
@@ -12,31 +14,104 @@ 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, _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 terminalNodeImpl = GetByValNodeForArgCtx(argCtxt);
3130

32-
var selection = Selection.Selection;
31+
var replacementLine = GenerateByRefReplacementLine(terminalNodeImpl);
3332

34-
var module = Selection.QualifiedName.Component.CodeModule;
33+
ReplaceModuleLine(terminalNodeImpl.Symbol.Line, replacementLine);
34+
35+
}
36+
private ArgContext GetArgContextForIdentifier(ParserRuleContext context, string identifier)
37+
{
38+
var procStmtCtx = (ParserRuleContext)context.Parent.Parent;
39+
var procStmtCtxChildren = procStmtCtx.children;
40+
for (int idx = 0; idx < procStmtCtxChildren.Count; idx++)
41+
{
42+
if (procStmtCtxChildren[idx] is SubstmtContext)
43+
{
44+
var procStmtCtxChild = (SubstmtContext)procStmtCtxChildren[idx];
45+
var arg = procStmtCtxChild.children;
46+
for (int idx2 = 0; idx2 < arg.Count; idx2++)
47+
{
48+
if (arg[idx2] is ArgContext)
49+
{
50+
var name = GetIdentifierNameFor((ArgContext)arg[idx2]);
51+
if (name.Equals(identifier))
52+
{
53+
return (ArgContext)arg[idx2];
54+
}
55+
}
56+
}
57+
}
58+
}
59+
return null;
60+
}
61+
private string GetIdentifierNameFor(ArgContext argCtxt)
62+
{
63+
var argCtxtChild = argCtxt.children;
64+
var idRef = GetUnRestrictedIdentifierCtx(argCtxt);
65+
return idRef.GetText();
66+
}
67+
private UnrestrictedIdentifierContext GetUnRestrictedIdentifierCtx(ArgContext argCtxt)
68+
{
69+
var argCtxtChild = argCtxt.children;
70+
for (int idx = 0; idx < argCtxtChild.Count; idx++)
3571
{
36-
var lines = module.GetLines(selection.StartLine, selection.LineCount);
37-
var result = lines.Replace(parameter, newContent);
38-
module.ReplaceLine(selection.StartLine, result);
72+
if (argCtxtChild[idx] is UnrestrictedIdentifierContext)
73+
{
74+
return (UnrestrictedIdentifierContext)argCtxtChild[idx];
75+
}
3976
}
77+
return null;
78+
}
79+
private TerminalNodeImpl GetByValNodeForArgCtx(ArgContext argCtxt)
80+
{
81+
var argCtxtChild = argCtxt.children;
82+
for (int idx = 0; idx < argCtxtChild.Count; idx++)
83+
{
84+
if (argCtxtChild[idx] is TerminalNodeImpl)
85+
{
86+
var candidate = (TerminalNodeImpl)argCtxtChild[idx];
87+
if (candidate.Symbol.Text.Equals(Tokens.ByVal))
88+
{
89+
return candidate;
90+
}
91+
}
92+
}
93+
return null;
94+
}
95+
private string GenerateByRefReplacementLine(TerminalNodeImpl terminalNodeImpl)
96+
{
97+
var module = Selection.QualifiedName.Component.CodeModule;
98+
var byValTokenLine = module.GetLines(terminalNodeImpl.Symbol.Line, 1);
99+
100+
return ReplaceAtIndex(byValTokenLine, Tokens.ByVal, Tokens.ByRef, terminalNodeImpl.Symbol.Column);
101+
}
102+
private string ReplaceAtIndex(string input, string toReplace, string replacement, int index)
103+
{
104+
int stopIndex = index + toReplace.Length;
105+
var prefix = input.Substring(0, index);
106+
var suffix = input.Substring(stopIndex + 1);
107+
var target = input.Substring(index, stopIndex - index + 1);
108+
return prefix + target.Replace(toReplace, replacement) + suffix;
109+
}
110+
private void ReplaceModuleLine(int lineNumber, string replacementLine)
111+
{
112+
var module = Selection.QualifiedName.Component.CodeModule;
113+
module.DeleteLines(lineNumber);
114+
module.InsertLines(lineNumber, replacementLine);
40115
}
41116
}
42117
}

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
}

RetailCoder.VBE/Inspections/Results/ProcedureCanBeWrittenAsFunctionInspectionResult.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -16,12 +16,12 @@ namespace Rubberduck.Inspections.Results
1616
public class ProcedureCanBeWrittenAsFunctionInspectionResult : InspectionResultBase
1717
{
1818
private IEnumerable<QuickFixBase> _quickFixes;
19-
private readonly QualifiedContext<VBAParser.ArgListContext> _argListQualifiedContext;
19+
private readonly QualifiedContext<VBAParser.SubstmtContext> _argListQualifiedContext;
2020
private readonly QualifiedContext<VBAParser.SubStmtContext> _subStmtQualifiedContext;
2121
private readonly RubberduckParserState _state;
2222

2323
public ProcedureCanBeWrittenAsFunctionInspectionResult(IInspection inspection, RubberduckParserState state,
24-
QualifiedContext<VBAParser.ArgListContext> argListQualifiedContext, QualifiedContext<VBAParser.SubStmtContext> subStmtQualifiedContext)
24+
QualifiedContext<VBAParser.SubstmtContext> argListQualifiedContext, QualifiedContext<VBAParser.SubStmtContext> subStmtQualifiedContext)
2525
: base(inspection, subStmtQualifiedContext.ModuleName, subStmtQualifiedContext.Context.subroutineName())
2626
{
2727
_target = state.AllUserDeclarations.Single(declaration => declaration.DeclarationType == DeclarationType.Procedure
@@ -57,14 +57,14 @@ public class ChangeProcedureToFunction : QuickFixBase
5757
public override bool CanFixInProject { get { return false; } }
5858

5959
private readonly RubberduckParserState _state;
60-
private readonly QualifiedContext<VBAParser.ArgListContext> _argListQualifiedContext;
60+
private readonly QualifiedContext<VBAParser.SubstmtContext> _argListQualifiedContext;
6161
private readonly QualifiedContext<VBAParser.SubStmtContext> _subStmtQualifiedContext;
6262
private readonly QualifiedContext<VBAParser.ArgContext> _argQualifiedContext;
6363

6464
private int _lineOffset;
6565

6666
public ChangeProcedureToFunction(RubberduckParserState state,
67-
QualifiedContext<VBAParser.ArgListContext> argListQualifiedContext,
67+
QualifiedContext<VBAParser.SubstmtContext> argListQualifiedContext,
6868
QualifiedContext<VBAParser.SubStmtContext> subStmtQualifiedContext,
6969
QualifiedSelection selection)
7070
: base(subStmtQualifiedContext.Context, selection, InspectionsUI.ProcedureShouldBeFunctionInspectionQuickFix)

RetailCoder.VBE/Navigation/CodeExplorer/CodeExplorerMemberViewModel.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -117,7 +117,7 @@ public override string NameWithSignature
117117
}
118118

119119
var context =
120-
_declaration.Context.children.FirstOrDefault(d => d is VBAParser.ArgListContext) as VBAParser.ArgListContext;
120+
_declaration.Context.children.FirstOrDefault(d => d is VBAParser.SubstmtContext) as VBAParser.SubstmtContext;
121121

122122
if (context == null)
123123
{

RetailCoder.VBE/Refactorings/IntroduceParameter/IntroduceParameterRefactoring.cs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -142,7 +142,7 @@ private void UpdateSignature(Declaration targetVariable)
142142
var functionDeclaration = _declarations.FindTarget(targetVariable.QualifiedSelection, ValidDeclarationTypes);
143143

144144
var proc = (dynamic)functionDeclaration.Context;
145-
var paramList = (VBAParser.ArgListContext)proc.argList();
145+
var paramList = (VBAParser.SubstmtContext)proc.argList();
146146
var module = functionDeclaration.QualifiedName.QualifiedModuleName.Component.CodeModule;
147147
{
148148
var interfaceImplementation = GetInterfaceImplementation(functionDeclaration);
@@ -182,14 +182,14 @@ private void UpdateSignature(Declaration targetVariable)
182182
private void UpdateSignature(Declaration targetMethod, Declaration targetVariable)
183183
{
184184
var proc = (dynamic)targetMethod.Context;
185-
var paramList = (VBAParser.ArgListContext)proc.argList();
185+
var paramList = (VBAParser.SubstmtContext)proc.argList();
186186
var module = targetMethod.QualifiedName.QualifiedModuleName.Component.CodeModule;
187187
{
188188
AddParameter(targetMethod, targetVariable, paramList, module);
189189
}
190190
}
191191

192-
private void AddParameter(Declaration targetMethod, Declaration targetVariable, VBAParser.ArgListContext paramList, ICodeModule module)
192+
private void AddParameter(Declaration targetMethod, Declaration targetVariable, VBAParser.SubstmtContext paramList, ICodeModule module)
193193
{
194194
var argList = paramList.arg();
195195
var lastParam = argList.LastOrDefault();

RetailCoder.VBE/Refactorings/RemoveParameters/RemoveParametersRefactoring.cs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -279,7 +279,7 @@ private string GetOldSignature(Declaration target)
279279
private void AdjustSignatures()
280280
{
281281
var proc = (dynamic)_model.TargetDeclaration.Context;
282-
var paramList = (VBAParser.ArgListContext)proc.argList();
282+
var paramList = (VBAParser.SubstmtContext)proc.argList();
283283
var module = _model.TargetDeclaration.QualifiedName.QualifiedModuleName.Component.CodeModule;
284284
{
285285
// if we are adjusting a property getter, check if we need to adjust the letter/setter too
@@ -336,23 +336,23 @@ private void AdjustSignatures(Declaration declaration)
336336
var proc = (dynamic)declaration.Context.Parent;
337337
var module = declaration.QualifiedName.QualifiedModuleName.Component.CodeModule;
338338
{
339-
VBAParser.ArgListContext paramList;
339+
VBAParser.SubstmtContext paramList;
340340

341341
if (declaration.DeclarationType == DeclarationType.PropertySet
342342
|| declaration.DeclarationType == DeclarationType.PropertyLet)
343343
{
344-
paramList = (VBAParser.ArgListContext)proc.children[0].argList();
344+
paramList = (VBAParser.SubstmtContext)proc.children[0].argList();
345345
}
346346
else
347347
{
348-
paramList = (VBAParser.ArgListContext)proc.subStmt().argList();
348+
paramList = (VBAParser.SubstmtContext)proc.subStmt().argList();
349349
}
350350

351351
RemoveSignatureParameters(declaration, paramList, module);
352352
}
353353
}
354354

355-
private void RemoveSignatureParameters(Declaration target, VBAParser.ArgListContext paramList, ICodeModule module)
355+
private void RemoveSignatureParameters(Declaration target, VBAParser.SubstmtContext paramList, ICodeModule module)
356356
{
357357
// property set/let have one more parameter than is listed in the getter parameters
358358
var nonRemovedParamNames = paramList.arg().Where((a, s) => s >= _model.Parameters.Count || !_model.Parameters[s].IsRemoved).Select(s => s.GetText());

RetailCoder.VBE/Refactorings/Rename/RenameRefactoring.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -335,7 +335,7 @@ private void RenameDeclaration(Declaration target, string newName)
335335

336336
if (target.DeclarationType == DeclarationType.Parameter)
337337
{
338-
var argList = (VBAParser.ArgListContext)target.Context.Parent;
338+
var argList = (VBAParser.SubstmtContext)target.Context.Parent;
339339
var lineNum = argList.GetSelection().LineCount;
340340

341341
// delete excess lines to prevent removing our own changes

0 commit comments

Comments
 (0)