Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
Original file line number Diff line number Diff line change
Expand Up @@ -103,7 +103,7 @@ private void InsertLocalVariableDeclarationAndAssignment(IModuleRewriter rewrite
+ (_target.AsTypeDeclaration is ClassModuleDeclaration ? Tokens.Set + " " : string.Empty)
+ localIdentifier + " = " + _target.IdentifierName;

rewriter.InsertAtIndex("\r\n" + content, ((ParserRuleContext)_target.Context.Parent).Stop.TokenIndex + 1);
rewriter.Insert(((ParserRuleContext)_target.Context.Parent).Stop.TokenIndex + 1, "\r\n" + content);
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -66,11 +66,11 @@ private void AddProperty(IModuleRewriter rewriter)
var lastMember = members.LastOrDefault(m => m.DeclarationType.HasFlag(DeclarationType.Member));
if (lastMember == null)
{
rewriter.InsertAtIndex(property, 1);
rewriter.Insert(1, property);
}
else
{
rewriter.InsertAtIndex(property, lastMember.Context.Stop.TokenIndex);
rewriter.Insert(lastMember.Context.Stop.TokenIndex, property);
}
}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,7 @@ private void AddField(IModuleRewriter rewriter, Declaration target)
.OrderByDescending(item => item.Selection);

var firstMember = members.FirstOrDefault();
rewriter.InsertAtIndex(content, firstMember?.Context.Start.TokenIndex ?? 0);
rewriter.Insert(firstMember?.Context.Start.TokenIndex ?? 0, content);
}
}
}
Original file line number Diff line number Diff line change
@@ -1,10 +1,8 @@
using System;
using System.Collections.Generic;
using System.Collections.Generic;
using System.Linq;
using System.Windows.Forms;
using Rubberduck.Common;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.PostProcessing;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.UI;
Expand Down Expand Up @@ -105,7 +103,7 @@ private void PromoteVariable(Declaration target)
oldSelection = module.GetQualifiedSelection();
}

UpdateSignature(rewriter, target);
UpdateSignature(target);
rewriter.Remove(target);

if (oldSelection.HasValue)
Expand Down Expand Up @@ -133,7 +131,7 @@ private bool PromptIfMethodImplementsInterface(Declaration targetVariable)
return introduceParamToInterface != DialogResult.No;
}

private void UpdateSignature(IModuleRewriter rewriter, Declaration targetVariable)
private void UpdateSignature(Declaration targetVariable)
{
var functionDeclaration = _declarations.FindTarget(targetVariable.QualifiedSelection, ValidDeclarationTypes);

Expand All @@ -145,7 +143,7 @@ private void UpdateSignature(IModuleRewriter rewriter, Declaration targetVariabl
functionDeclaration.DeclarationType != DeclarationType.PropertyLet &&
functionDeclaration.DeclarationType != DeclarationType.PropertySet)
{
AddParameter(rewriter, functionDeclaration, targetVariable, paramList);
AddParameter(functionDeclaration, targetVariable, paramList);

if (interfaceImplementation == null)
{
Expand All @@ -157,15 +155,15 @@ private void UpdateSignature(IModuleRewriter rewriter, Declaration targetVariabl
functionDeclaration.DeclarationType == DeclarationType.PropertyLet ||
functionDeclaration.DeclarationType == DeclarationType.PropertySet)
{
UpdateProperties(rewriter, functionDeclaration, targetVariable);
UpdateProperties(functionDeclaration, targetVariable);
}

if (interfaceImplementation == null)
{
return;
}

UpdateSignature(rewriter, interfaceImplementation, targetVariable);
UpdateSignature(interfaceImplementation, targetVariable);

var interfaceImplementations = _declarations.FindInterfaceImplementationMembers()
.Where(item => item.ProjectId == interfaceImplementation.ProjectId
Expand All @@ -176,45 +174,41 @@ private void UpdateSignature(IModuleRewriter rewriter, Declaration targetVariabl

foreach (var implementation in interfaceImplementations)
{
UpdateSignature(rewriter, implementation, targetVariable);
UpdateSignature(implementation, targetVariable);
}
}

private void UpdateSignature(IModuleRewriter rewriter, Declaration targetMethod, Declaration targetVariable)
private void UpdateSignature(Declaration targetMethod, Declaration targetVariable)
{
var proc = (dynamic) targetMethod.Context;
var paramList = (VBAParser.ArgListContext) proc.argList();
AddParameter(rewriter, targetMethod, targetVariable, paramList);
AddParameter(targetMethod, targetVariable, paramList);
}

private void AddParameter(IModuleRewriter rewriter, Declaration targetMethod, Declaration targetVariable, VBAParser.ArgListContext paramList)
private void AddParameter(Declaration targetMethod, Declaration targetVariable, VBAParser.ArgListContext paramList)
{
var rewriter = _state.GetRewriter(targetMethod);

var argList = paramList.arg();
var lastParam = argList.LastOrDefault();
var newParameter = Tokens.ByVal + " " + targetVariable.IdentifierName + " "+ Tokens.As + " " + targetVariable.AsTypeName;
var newContent = paramList.GetText(); //GetOldSignature(rewriter, targetMethod);

if (lastParam == null)
if (!argList.Any())
{
// offset 1-based index:
newContent = newContent.Insert(newContent.IndexOf('(') + 1, newParameter);
rewriter.Insert(paramList.RPAREN().Symbol.TokenIndex, newParameter);
}
else if (targetMethod.DeclarationType != DeclarationType.PropertyLet &&
targetMethod.DeclarationType != DeclarationType.PropertySet)
{
newContent = newContent.Replace(argList.Last().GetText(),
argList.Last().GetText() + ", " + newParameter);
rewriter.Insert(paramList.RPAREN().Symbol.TokenIndex, $", {newParameter}");
}
else
{
newContent = newContent.Replace(argList.Last().GetText(),
newParameter + ", " + argList.Last().GetText());
var lastParam = argList.Last();
rewriter.Insert(lastParam.Start.TokenIndex, $"{newParameter}, ");
}

rewriter.Replace(paramList, newContent);
}

private void UpdateProperties(IModuleRewriter rewriter, Declaration knownProperty, Declaration targetVariable)
private void UpdateProperties(Declaration knownProperty, Declaration targetVariable)
{
var propertyGet = _declarations.FirstOrDefault(d =>
d.DeclarationType == DeclarationType.PropertyGet &&
Expand Down Expand Up @@ -252,51 +246,8 @@ private void UpdateProperties(IModuleRewriter rewriter, Declaration knownPropert
properties.OrderByDescending(o => o.Selection.StartLine)
.ThenByDescending(t => t.Selection.StartColumn))
{
UpdateSignature(rewriter, property, targetVariable);
}
}

private string GetOldSignature(IModuleRewriter rewriter, Declaration target)
{
var context = target.Context;
var firstTokenIndex = context.Start.TokenIndex;
var lastTokenIndex = -1; // will blow up if this code runs for any context other than below

var subStmtContext = context as VBAParser.SubStmtContext;
if (subStmtContext != null)
{
lastTokenIndex = subStmtContext.argList().RPAREN().Symbol.TokenIndex;
}

var functionStmtContext = context as VBAParser.FunctionStmtContext;
if (functionStmtContext != null)
{
lastTokenIndex = functionStmtContext.asTypeClause() != null
? functionStmtContext.asTypeClause().Stop.TokenIndex
: functionStmtContext.argList().RPAREN().Symbol.TokenIndex;
UpdateSignature(property, targetVariable);
}

var propertyGetStmtContext = context as VBAParser.PropertyGetStmtContext;
if (propertyGetStmtContext != null)
{
lastTokenIndex = propertyGetStmtContext.asTypeClause() != null
? propertyGetStmtContext.asTypeClause().Stop.TokenIndex
: propertyGetStmtContext.argList().RPAREN().Symbol.TokenIndex;
}

var propertyLetStmtContext = context as VBAParser.PropertyLetStmtContext;
if (propertyLetStmtContext != null)
{
lastTokenIndex = propertyLetStmtContext.argList().RPAREN().Symbol.TokenIndex;
}

var propertySetStmtContext = context as VBAParser.PropertySetStmtContext;
if (propertySetStmtContext != null)
{
lastTokenIndex = propertySetStmtContext.argList().RPAREN().Symbol.TokenIndex;
}

return rewriter.GetText(firstTokenIndex, lastTokenIndex);
}

private Declaration GetInterfaceImplementation(Declaration target)
Expand Down
4 changes: 2 additions & 2 deletions Rubberduck.Parsing/PostProcessing/IModuleRewriter.cs
Original file line number Diff line number Diff line change
Expand Up @@ -52,9 +52,9 @@ public interface IModuleRewriter
/// <summary>
/// Inserts specified content at the specified token index in the module. Use <see cref="Rewrite"/> method to apply changes.
/// </summary>
/// <param name="content">The literal content to insert.</param>
/// <param name="tokenIndex">The index of the insertion point in the module's lexer token stream.</param>
void InsertAtIndex(string content, int tokenIndex);
/// <param name="content">The literal content to insert.</param>
void Insert(int tokenIndex, string content);

/// <summary>
/// Gets the text between specified token positions (inclusive).
Expand Down
2 changes: 1 addition & 1 deletion Rubberduck.Parsing/PostProcessing/ModuleRewriter.cs
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@ public void Replace(IToken token, string content)
_rewriter.Replace(token, content);
}

public void InsertAtIndex(string content, int tokenIndex)
public void Insert(int tokenIndex, string content)
{
_rewriter.InsertBefore(tokenIndex, content);
}
Expand Down
13 changes: 6 additions & 7 deletions RubberduckTests/Refactoring/IntroduceParameterTests.cs
Original file line number Diff line number Diff line change
@@ -1,9 +1,7 @@
using System;
using System.Linq;
using System.Windows.Forms;
using Microsoft.VisualStudio.TestTools.UnitTesting;
using Moq;
using Rubberduck.Common;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Refactorings.IntroduceParameter;
using Rubberduck.UI;
Expand Down Expand Up @@ -454,8 +452,9 @@ Sub IClass1_fizz(ByVal boo As Boolean, ByVal fizz As Date)
.AddComponent("Class1", ComponentType.ClassModule, inputCode2)
.Build();
var vbe = builder.AddProject(project).Build();
var component = project.Object.VBComponents[1];
vbe.Setup(v => v.ActiveCodePane).Returns(component.CodeModule.CodePane);
var component0 = project.Object.VBComponents[0];
var component1 = project.Object.VBComponents[1];
vbe.Setup(v => v.ActiveCodePane).Returns(component1.CodeModule.CodePane);

var state = MockParser.CreateAndParse(vbe.Object);

Expand All @@ -468,10 +467,10 @@ Sub IClass1_fizz(ByVal boo As Boolean, ByVal fizz As Date)
var target = state.AllUserDeclarations.SingleOrDefault(e => e.IdentifierName == "fizz" && e.DeclarationType == DeclarationType.Variable);
refactoring.Refactor(target);

var rewriter1 = state.GetRewriter(component);
var rewriter1 = state.GetRewriter(component0);
Assert.AreEqual(expectedCode1, rewriter1.GetText());

var rewriter2 = state.GetRewriter(component);
var rewriter2 = state.GetRewriter(component1);
Assert.AreEqual(expectedCode2, rewriter2.GetText());
}

Expand Down Expand Up @@ -634,7 +633,7 @@ Dim bar As Boolean
.Returns(DialogResult.OK);

var refactoring = new IntroduceParameterRefactoring(vbe.Object, state, messageBox.Object);
refactoring.Refactor(state.AllUserDeclarations.First(d => d.DeclarationType == DeclarationType.Variable));
refactoring.Refactor(state.AllUserDeclarations.First(d => d.DeclarationType != DeclarationType.Variable));

messageBox.Verify(m =>
m.Show(It.IsAny<string>(), It.IsAny<string>(), It.IsAny<MessageBoxButtons>(),
Expand Down