Skip to content

Commit 43a47d0

Browse files
committed
fixes issue with renaming a parameter whose identifier name appeared elsewhere in a signature (i.e. not as a usage of that parameter); this breaks RenamePresenter tests (commented out)
1 parent f929c29 commit 43a47d0

File tree

5 files changed

+335
-245
lines changed

5 files changed

+335
-245
lines changed

RetailCoder.VBE/UI/RefactorMenu.cs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -154,7 +154,8 @@ public void Rename(QualifiedSelection selection)
154154
{
155155
using (var view = new RenameDialog())
156156
{
157-
var presenter = new RenamePresenter(IDE, view, _parser.Parse(IDE.ActiveVBProject).Declarations, selection);
157+
var parseResult = _parser.Parse(IDE.ActiveVBProject);
158+
var presenter = new RenamePresenter(IDE, view, parseResult, selection);
158159
presenter.Show();
159160
}
160161
}
@@ -163,7 +164,8 @@ public void Rename(Declaration target)
163164
{
164165
using (var view = new RenameDialog())
165166
{
166-
var presenter = new RenamePresenter(IDE, view, _parser.Parse(IDE.ActiveVBProject).Declarations, new QualifiedSelection(target.QualifiedName.QualifiedModuleName, target.Selection));
167+
var parseResult = _parser.Parse(IDE.ActiveVBProject);
168+
var presenter = new RenamePresenter(IDE, view, parseResult, new QualifiedSelection(target.QualifiedName.QualifiedModuleName, target.Selection));
167169
presenter.Show(target);
168170
}
169171
}

RetailCoder.VBE/UI/Refactorings/Rename/RenamePresenter.cs

Lines changed: 90 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,8 @@
33
using System.Runtime.InteropServices;
44
using System.Text.RegularExpressions;
55
using System.Windows.Forms;
6+
using Antlr4.Runtime;
7+
using Antlr4.Runtime.Misc;
68
using Microsoft.Vbe.Interop;
79
using Rubberduck.Extensions;
810
using Rubberduck.Parsing;
@@ -17,14 +19,16 @@ public class RenamePresenter
1719
private readonly IRenameView _view;
1820
private readonly Declarations _declarations;
1921
private readonly QualifiedSelection _selection;
22+
private readonly VBProjectParseResult _parseResult;
2023

21-
public RenamePresenter(VBE vbe, IRenameView view, Declarations declarations, QualifiedSelection selection)
24+
public RenamePresenter(VBE vbe, IRenameView view, VBProjectParseResult parseResult, QualifiedSelection selection)
2225
{
2326
_vbe = vbe;
2427
_view = view;
2528
_view.OkButtonClicked += OnOkButtonClicked;
2629

27-
_declarations = declarations;
30+
_parseResult = parseResult;
31+
_declarations = parseResult.Declarations;
2832
_selection = selection;
2933
}
3034

@@ -86,8 +90,7 @@ private void RenameDeclaration()
8690
}
8791

8892
var module = _vbe.FindCodeModules(_view.Target.QualifiedName.QualifiedModuleName).First();
89-
var content = module.get_Lines(_view.Target.Selection.StartLine, 1);
90-
var newContent = GetReplacementLine(content, _view.Target.IdentifierName, _view.NewName);
93+
var newContent = GetReplacementLine(module, _view.Target, _view.NewName);
9194
module.ReplaceLine(_view.Target.Selection.StartLine, newContent);
9295
}
9396

@@ -184,6 +187,89 @@ private string GetReplacementLine(string content, string target, string newName)
184187
return Regex.Replace(content, "\\b" + target + "\\b", newName);
185188
}
186189

190+
private string GetReplacementLine(CodeModule module, Declaration target, string newName)
191+
{
192+
var targetModule = _parseResult.ComponentParseResults.SingleOrDefault(m => m.QualifiedName == _view.Target.QualifiedName.QualifiedModuleName);
193+
if (targetModule == null)
194+
{
195+
return null;
196+
}
197+
198+
var content = module.get_Lines(_view.Target.Selection.StartLine, 1);
199+
200+
if (target.DeclarationType == DeclarationType.Parameter)
201+
{
202+
var argContext = (VBAParser.ArgContext)_view.Target.Context;
203+
targetModule.Rewriter.Replace(argContext.ambiguousIdentifier().Start.TokenIndex, _view.NewName);
204+
205+
// Target.Context is an ArgContext, its parent is an ArgsListContext;
206+
// the ArgsListContext's parent is the procedure context and it includes the body.
207+
var context = (ParserRuleContext) _view.Target.Context.Parent.Parent;
208+
var firstTokenIndex = context.Start.TokenIndex;
209+
var lastTokenIndex = -1; // will blow up if this code runs for any context other than below
210+
211+
var subStmtContext = context as VBAParser.SubStmtContext;
212+
if (subStmtContext != null)
213+
{
214+
lastTokenIndex = subStmtContext.argList().RPAREN().Symbol.TokenIndex;
215+
}
216+
217+
var functionStmtContext = context as VBAParser.FunctionStmtContext;
218+
if (functionStmtContext != null)
219+
{
220+
lastTokenIndex = functionStmtContext.asTypeClause() != null
221+
? functionStmtContext.asTypeClause().Stop.TokenIndex
222+
: functionStmtContext.argList().RPAREN().Symbol.TokenIndex;
223+
}
224+
225+
var propertyGetStmtContext = context as VBAParser.PropertyGetStmtContext;
226+
if (propertyGetStmtContext != null)
227+
{
228+
lastTokenIndex = propertyGetStmtContext.asTypeClause() != null
229+
? propertyGetStmtContext.asTypeClause().Stop.TokenIndex
230+
: propertyGetStmtContext.argList().RPAREN().Symbol.TokenIndex;
231+
}
232+
233+
var propertyLetStmtContext = context as VBAParser.PropertyLetStmtContext;
234+
if (propertyLetStmtContext != null)
235+
{
236+
lastTokenIndex = propertyLetStmtContext.argList().RPAREN().Symbol.TokenIndex;
237+
}
238+
239+
var propertySetStmtContext = context as VBAParser.PropertySetStmtContext;
240+
if (propertySetStmtContext != null)
241+
{
242+
lastTokenIndex = propertySetStmtContext.argList().RPAREN().Symbol.TokenIndex;
243+
}
244+
245+
var declareStmtContext = context as VBAParser.DeclareStmtContext;
246+
if (declareStmtContext != null)
247+
{
248+
lastTokenIndex = declareStmtContext.STRINGLITERAL().Last().Symbol.TokenIndex;
249+
if (declareStmtContext.argList() != null)
250+
{
251+
lastTokenIndex = declareStmtContext.argList().RPAREN().Symbol.TokenIndex;
252+
}
253+
if (declareStmtContext.asTypeClause() != null)
254+
{
255+
lastTokenIndex = declareStmtContext.asTypeClause().Stop.TokenIndex;
256+
}
257+
}
258+
259+
var eventStmtContext = context as VBAParser.EventStmtContext;
260+
if (eventStmtContext != null)
261+
{
262+
lastTokenIndex = eventStmtContext.argList().RPAREN().Symbol.TokenIndex;
263+
}
264+
265+
return targetModule.Rewriter.GetText(new Interval(firstTokenIndex, lastTokenIndex));
266+
}
267+
else
268+
{
269+
return GetReplacementLine(content, target.IdentifierName, newName);
270+
}
271+
}
272+
187273
private static readonly DeclarationType[] ProcedureDeclarationTypes =
188274
{
189275
DeclarationType.Procedure,

RetailCoder.VBE/VBA/RubberduckParser.cs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -33,12 +33,13 @@ public VBProjectParseResult Parse(VBProject project)
3333
return new VBProjectParseResult(results);
3434
}
3535

36-
private IParseTree Parse(string code)
36+
private IParseTree Parse(string code, out TokenStreamRewriter outRewriter)
3737
{
3838
var input = new AntlrInputStream(code);
3939
var lexer = new VBALexer(input);
4040
var tokens = new CommonTokenStream(lexer);
4141
var parser = new VBAParser(tokens);
42+
outRewriter = new TokenStreamRewriter(tokens);
4243

4344
var result = parser.startRule();
4445
return result;
@@ -55,9 +56,10 @@ private VBComponentParseResult Parse(VBComponent component)
5556
return cachedValue;
5657
}
5758

58-
var parseTree = Parse(CodeModuleExtensions.Lines(component.CodeModule));
59+
TokenStreamRewriter rewriter;
60+
var parseTree = Parse(CodeModuleExtensions.Lines(component.CodeModule), out rewriter);
5961
var comments = ParseComments(component);
60-
var result = new VBComponentParseResult(component, parseTree, comments);
62+
var result = new VBComponentParseResult(component, parseTree, comments, rewriter);
6163

6264
ParseResultCache.AddOrUpdate(name, module => result, (qName, module) => result);
6365
return result;

Rubberduck.Parsing/VBComponentParseResult.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -8,13 +8,13 @@ namespace Rubberduck.Parsing
88
{
99
public class VBComponentParseResult
1010
{
11-
public VBComponentParseResult(VBComponent component, IParseTree parseTree, IEnumerable<CommentNode> comments, ParserRuleContext context = null)
11+
public VBComponentParseResult(VBComponent component, IParseTree parseTree, IEnumerable<CommentNode> comments, TokenStreamRewriter rewriter)
1212
{
1313
_component = component;
1414
_qualifiedName = component.QualifiedName();
1515
_parseTree = parseTree;
1616
_comments = comments;
17-
_context = context;
17+
_rewriter = rewriter;
1818
}
1919

2020
private readonly VBComponent _component;
@@ -29,7 +29,7 @@ public VBComponentParseResult(VBComponent component, IParseTree parseTree, IEnum
2929
private IEnumerable<CommentNode> _comments;
3030
public IEnumerable<CommentNode> Comments { get { return _comments; } }
3131

32-
private ParserRuleContext _context;
33-
public ParserRuleContext Context { get { return _context; } }
32+
private readonly TokenStreamRewriter _rewriter;
33+
public TokenStreamRewriter Rewriter { get { return _rewriter; } }
3434
}
3535
}

0 commit comments

Comments
 (0)