Skip to content

Commit

Permalink
Merge pull request #3973 from tommy9/MoveCloserIndentFix
Browse files Browse the repository at this point in the history
Move closer refactoring indent fix
  • Loading branch information
Hosch250 committed Apr 29, 2018
2 parents 1b1fe5c + 22181b0 commit a154ce8
Show file tree
Hide file tree
Showing 3 changed files with 68 additions and 18 deletions.
Expand Up @@ -125,6 +125,7 @@ private void MoveCloserToUsage()
{
rewriter.Rewrite();
}
Reparse();
}

private void UpdateOtherModules()
Expand Down Expand Up @@ -168,9 +169,19 @@ private void InsertNewDeclaration()
}

var insertionIndex = (expression as ParserRuleContext).Start.TokenIndex;
int indentLength;
using (var pane = _vbe.ActiveCodePane)
{
using (var codeModule = pane.CodeModule)
{
var firstReferenceLine = codeModule.GetLines((expression as ParserRuleContext).Start.Line, 1);
indentLength = firstReferenceLine.Length - firstReferenceLine.TrimStart().Length;
}
}
var padding = new string(' ', indentLength);

var rewriter = _state.GetRewriter(firstReference.QualifiedModuleName);
rewriter.InsertBefore(insertionIndex, newVariable);
rewriter.InsertBefore(insertionIndex, newVariable + padding);

_rewriters.Add(rewriter);
}
Expand Down Expand Up @@ -205,5 +216,10 @@ private void UpdateCallsToOtherModule(IEnumerable<IdentifierReference> reference
_rewriters.Add(rewriter);
}
}

private void Reparse()
{
_state.OnParseRequested(this);
}
}
}
Expand Up @@ -25,7 +25,7 @@ public void MoveFieldCloserToUsage_QuickFixWorks()
const string expectedCode =
@"Public Sub Foo()
Dim bar As String
bar = ""test""
bar = ""test""
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component);
Expand Down
66 changes: 50 additions & 16 deletions RubberduckTests/Refactoring/MoveCloserToUsageTests.cs
Expand Up @@ -32,7 +32,41 @@ public void MoveCloserToUsageRefactoring_Field()
const string expectedCode =
@"Private Sub Foo()
Dim bar As Boolean
bar = True
bar = True
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component, selection);
using (var state = MockParser.CreateAndParse(vbe.Object))
{

var qualifiedSelection = new QualifiedSelection(new QualifiedModuleName(component), selection);

var refactoring = new MoveCloserToUsageRefactoring(vbe.Object, state, null);
refactoring.Refactor(qualifiedSelection);

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

[Test]
[Category("Refactorings")]
[Category("Move Closer")]
public void MoveCloserToUsageRefactoring_LineNumbers()
{
//Input
const string inputCode =
@"Private bar As Boolean
Private Sub Foo()
100 bar = True
End Sub";
var selection = new Selection(1, 1);

//Expectation
const string expectedCode =
@"Private Sub Foo()
Dim bar As Boolean
100 bar = True
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component, selection);
Expand Down Expand Up @@ -69,7 +103,7 @@ As _
const string expectedCode =
@"Private Sub Foo()
Dim bar As Boolean
bar = True
bar = True
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component, selection);
Expand Down Expand Up @@ -155,7 +189,7 @@ public void MoveCloserToUsageRefactoring_Variable()
@"Private Sub Foo()
Dim bat As Integer
Dim bar As Boolean
bar = True
bar = True
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component, selection);
Expand Down Expand Up @@ -194,7 +228,7 @@ As _
@"Private Sub Foo()
Dim bat As Integer
Dim bar As Boolean
bar = True
bar = True
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component, selection);
Expand Down Expand Up @@ -234,7 +268,7 @@ public void MoveCloserToUsageRefactoring_MultipleFields_MoveSecond()
Private Sub Foo()
Dim bat As Boolean
bat = True
bat = True
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component, selection);
Expand Down Expand Up @@ -274,7 +308,7 @@ public void MoveCloserToUsageRefactoring_MultipleFieldsOneStatement_MoveFirst()
Private Sub Foo()
Dim bar As Integer
bar = 3
bar = 3
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component, selection);
Expand Down Expand Up @@ -314,7 +348,7 @@ public void MoveCloserToUsageRefactoring_MultipleFieldsOneStatement_MoveSecond()
Private Sub Foo()
Dim bat As Boolean
bat = True
bat = True
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component, selection);
Expand Down Expand Up @@ -354,7 +388,7 @@ public void MoveCloserToUsageRefactoring_MultipleFieldsOneStatement_MoveLast()
Private Sub Foo()
Dim bay As Date
bay = #1/13/2004#
bay = #1/13/2004#
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component, selection);
Expand Down Expand Up @@ -396,7 +430,7 @@ public void MoveCloserToUsageRefactoring_MultipleVariablesOneStatement_MoveFirst
bat = True
Dim bar As Integer
bar = 3
bar = 3
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component, selection);
Expand Down Expand Up @@ -438,7 +472,7 @@ public void MoveCloserToUsageRefactoring_MultipleVariablesOneStatement_MoveSecon
bar = 1
Dim bat As Boolean
bat = True
bat = True
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component, selection);
Expand Down Expand Up @@ -480,7 +514,7 @@ public void MoveCloserToUsageRefactoring_MultipleVariablesOneStatement_MoveLast(
bar = 4
Dim bay As Date
bay = #1/13/2004#
bay = #1/13/2004#
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component, selection);
Expand Down Expand Up @@ -583,7 +617,7 @@ public void MoveCloserToUsageRefactoring_ReferenceIsNotBeginningOfStatement_Assi
const string expectedCode =
@"Private Sub Foo(ByRef bat As Boolean)
Dim bar As Boolean
bat = bar
bat = bar
End Sub";
var selection = new Selection(1, 1);

Expand Down Expand Up @@ -618,7 +652,7 @@ Sub Baz(ByVal bat As Boolean)
const string expectedCode =
@"Private Sub Foo()
Dim bar As Boolean
Baz bar
Baz bar
End Sub
Sub Baz(ByVal bat As Boolean)
End Sub";
Expand Down Expand Up @@ -657,7 +691,7 @@ Sub Baz(ByVal bat As Boolean, ByVal bas As Boolean, ByVal bac As Boolean)
const string expectedCode =
@"Private Sub Foo()
Dim bar As Boolean
Baz True, _
Baz True, _
True, _
bar
End Sub
Expand Down Expand Up @@ -735,7 +769,7 @@ Debug.Print someParam
@"
Public Sub Test()
Dim foo As Long
SomeSub someParam:=foo
SomeSub someParam:=foo
End Sub
Public Sub SomeSub(ByVal someParam As Long)
Expand Down Expand Up @@ -906,7 +940,7 @@ End Property
Debug.Print ""Some statements between""
Debug.Print ""Declaration and first usage!""
Dim foo As Class1
Set foo = new Class1
Set foo = new Class1
foo.Name = ""FooName""
foo.OtherProperty = 1626
End Sub";
Expand Down

0 comments on commit a154ce8

Please sign in to comment.