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(content, ((ParserRuleContext)_target.Context.Parent).Start.TokenIndex);
rewriter.InsertAtIndex("\r\n" + content, ((ParserRuleContext)_target.Context.Parent).Stop.TokenIndex + 1);
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@ public void Refactor(Declaration target)
_messageBox.Show(RubberduckUI.PromoteVariable_InvalidSelection, RubberduckUI.IntroduceParameter_Caption,
MessageBoxButtons.OK, MessageBoxIcon.Exclamation);

throw new ArgumentException(@"Invalid declaration type", "target");
return;
}

PromoteVariable(target);
Expand Down Expand Up @@ -112,8 +112,6 @@ private void PromoteVariable(Declaration target)
{
pane.Selection = oldSelection.Value.Selection;
}

_state.OnParseRequested(this);
}

private bool PromptIfMethodImplementsInterface(Declaration targetVariable)
Expand Down Expand Up @@ -194,7 +192,7 @@ private void AddParameter(IModuleRewriter rewriter, Declaration targetMethod, De
var argList = paramList.arg();
var lastParam = argList.LastOrDefault();
var newParameter = Tokens.ByVal + " " + targetVariable.IdentifierName + " "+ Tokens.As + " " + targetVariable.AsTypeName;
var newContent = GetOldSignature(rewriter, targetMethod);
var newContent = paramList.GetText(); //GetOldSignature(rewriter, targetMethod);

if (lastParam == null)
{
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -66,9 +66,7 @@ public void Refactor(Declaration target)
{
_messageBox.Show(RubberduckUI.MoveCloserToUsage_InvalidSelection, RubberduckUI.IntroduceParameter_Caption,
MessageBoxButtons.OK, MessageBoxIcon.Exclamation);

// ReSharper disable once LocalizableElement
throw new ArgumentException("Invalid Argument. DeclarationType must be 'Variable'", "target");
return;
}

_target = target;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -187,7 +187,7 @@ public void ConstantNotUsed_QuickFixWorks()
{
const string inputCode =
@"Public Sub Foo()
Const const1 As Integer = 9
Const const1 As Integer = 9
End Sub";

const string expectedCode =
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -269,7 +269,9 @@ public void ProcedureNotUsed_QuickFixWorks()
var inspectionResults = inspection.GetInspectionResults();

inspectionResults.First().QuickFixes.First().Fix();
Assert.AreEqual(expectedCode, component.CodeModule.Content());

var rewriter = state.GetRewriter(component);
Assert.AreEqual(expectedCode, rewriter.GetText());
}

[TestMethod]
Expand Down
28 changes: 14 additions & 14 deletions RubberduckTests/Inspections/VariableNotAssignedInspectionTests.cs
Original file line number Diff line number Diff line change
Expand Up @@ -98,8 +98,8 @@ public void VariableNotAssigned_Ignored_DoesNotReturnResult()
{
const string inputCode =
@"Sub Foo()
'@Ignore VariableNotAssigned
Dim var1 As String
'@Ignore VariableNotAssigned
Dim var1 As String
End Sub";

IVBComponent component;
Expand All @@ -118,7 +118,7 @@ public void UnassignedVariable_QuickFixWorks()
{
const string inputCode =
@"Sub Foo()
Dim var1 as Integer
Dim var1 as Integer
End Sub";

const string expectedCode =
Expand All @@ -140,10 +140,10 @@ public void UnassignedVariable_VariableOnMultipleLines_QuickFixWorks()
{
const string inputCode =
@"Sub Foo()
Dim _
var1 _
as _
Integer
Dim _
var1 _
as _
Integer
End Sub";

const string expectedCode =
Expand All @@ -165,13 +165,13 @@ public void UnassignedVariable_MultipleVariablesOnSingleLine_QuickFixWorks()
{
const string inputCode =
@"Sub Foo()
Dim var1 As Integer, var2 As Boolean
Dim var1 As Integer, var2 As Boolean
End Sub";

// note the extra space after "Integer"--the VBE will remove it
const string expectedCode =
@"Sub Foo()
Dim var1 As Integer
Dim var1 As Integer
End Sub";

IVBComponent component;
Expand All @@ -189,13 +189,13 @@ public void UnassignedVariable_MultipleVariablesOnMultipleLines_QuickFixWorks()
{
const string inputCode =
@"Sub Foo()
Dim var1 As Integer, _
var2 As Boolean
Dim var1 As Integer, _
var2 As Boolean
End Sub";

const string expectedCode =
@"Sub Foo()
Dim var1 As Integer
Dim var1 As Integer
End Sub";

IVBComponent component;
Expand All @@ -214,13 +214,13 @@ public void UnassignedVariable_IgnoreQuickFixWorks()
{
const string inputCode =
@"Sub Foo()
Dim var1 as Integer
Dim var1 as Integer
End Sub";

const string expectedCode =
@"Sub Foo()
'@Ignore VariableNotAssigned
Dim var1 as Integer
Dim var1 as Integer
End Sub";

IVBComponent component;
Expand Down
9 changes: 5 additions & 4 deletions RubberduckTests/Inspections/VariableNotUsedInspectionTests.cs
Original file line number Diff line number Diff line change
Expand Up @@ -148,7 +148,7 @@ public void UnassignedVariable_QuickFixWorks()
{
const string inputCode =
@"Sub Foo()
Dim var1 As String
Dim var1 As String
End Sub";

const string expectedCode =
Expand All @@ -162,7 +162,8 @@ Dim var1 As String
var inspection = new VariableNotUsedInspection(state);
inspection.GetInspectionResults().First().QuickFixes.First().Fix();

Assert.AreEqual(expectedCode, component.CodeModule.Content());
var rewriter = state.GetRewriter(component);
Assert.AreEqual(expectedCode, rewriter.GetText());
}

[TestMethod]
Expand All @@ -171,13 +172,13 @@ public void UnassignedVariable_IgnoreQuickFixWorks()
{
const string inputCode =
@"Sub Foo()
Dim var1 As String
Dim var1 As String
End Sub";

const string expectedCode =
@"Sub Foo()
'@Ignore VariableNotUsed
Dim var1 As String
Dim var1 As String
End Sub";

IVBComponent component;
Expand Down
Loading