Skip to content

Commit

Permalink
Remove blank lines left by declaration removals
Browse files Browse the repository at this point in the history
Incorporates IModuleRewriter extension method to clean up newlines left
by declaration removals.
  • Loading branch information
BZngr committed Aug 12, 2020
1 parent c935798 commit ef1c9cc
Show file tree
Hide file tree
Showing 3 changed files with 92 additions and 20 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Rewriter;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Refactorings.Common;

namespace Rubberduck.Refactorings.MoveCloserToUsage
{
Expand All @@ -16,12 +17,17 @@ public MoveCloserToUsageRefactoringAction(IRewritingManager rewritingManager)
protected override void Refactor(MoveCloserToUsageModel model, IRewriteSession rewriteSession)
{
var target = model.Target;
InsertNewDeclaration(target, rewriteSession);
RemoveOldDeclaration(target, rewriteSession);
UpdateQualifiedCalls(target, rewriteSession);
if (target is VariableDeclaration variable)
{
InsertNewDeclaration(variable, rewriteSession);
RemoveOldDeclaration(variable, rewriteSession);
UpdateQualifiedCalls(variable, rewriteSession);
return;
}
throw new ArgumentException("Invalid target declaration type");
}

private void InsertNewDeclaration(Declaration target, IRewriteSession rewriteSession)
private void InsertNewDeclaration(VariableDeclaration target, IRewriteSession rewriteSession)
{
var subscripts = target.Context.GetDescendent<VBAParser.SubscriptsContext>()?.GetText() ?? string.Empty;
var identifier = target.IsArray ? $"{target.IdentifierName}({subscripts})" : target.IdentifierName;
Expand Down Expand Up @@ -75,13 +81,22 @@ private string PaddedDeclaration(string declarationText, VBAParser.BlockStmtCont
return $"{declarationText}{Environment.NewLine}";
}

private void RemoveOldDeclaration(Declaration target, IRewriteSession rewriteSession)
private void RemoveOldDeclaration(VariableDeclaration target, IRewriteSession rewriteSession)
{
var rewriter = rewriteSession.CheckOutModuleRewriter(target.QualifiedModuleName);
rewriter.Remove(target);

//If a label precedes the declaration, then delete just the variable so that the line and label are retained.
if (target.Context.TryGetAncestor<VBAParser.BlockStmtContext>(out var blockContext)
&& blockContext.children.Any(c => c is VBAParser.StatementLabelDefinitionContext))
{
rewriter.Remove(target);
return;
}

rewriter.RemoveVariables(new VariableDeclaration[] { target });
}

private void UpdateQualifiedCalls(Declaration target, IRewriteSession rewriteSession)
private void UpdateQualifiedCalls(VariableDeclaration target, IRewriteSession rewriteSession)
{
var references = target.References.ToList();
var rewriter = rewriteSession.CheckOutModuleRewriter(references.First().QualifiedModuleName);
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@
using Rubberduck.CodeAnalysis.Inspections.Concrete;
using Rubberduck.CodeAnalysis.QuickFixes.Concrete.Refactoring;
using RubberduckTests.Mocks;
using Rubberduck.Interaction;
using Rubberduck.Parsing.VBA;
using Rubberduck.Refactorings.MoveCloserToUsage;
using Rubberduck.VBEditor;
Expand Down Expand Up @@ -55,8 +54,7 @@ End Sub
";

const string expectedCode =
@"
Public Sub Foo()
@"Public Sub Foo()
Dim bar As String
If bar = ""test"" Then Baz Else Foobar
End Sub
Expand Down Expand Up @@ -84,8 +82,7 @@ public void MoveFieldCloserToUsage_QuickFixWorks_SingleLineThenStatement()
End Sub";

const string expectedCode =
@"
Public Sub Foo()
@"Public Sub Foo()
Dim bar As String
If True Then bar = ""test""
End Sub";
Expand All @@ -106,8 +103,7 @@ public void MoveFieldCloserToUsage_QuickFixWorks_SingleLineElseStatement()
End Sub";

const string expectedCode =
@"
Public Sub Foo()
@"Public Sub Foo()
Dim bar As String
If True Then Else bar = ""test""
End Sub";
Expand Down
73 changes: 67 additions & 6 deletions RubberduckTests/Refactoring/MoveCloserToUsageTests.cs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,68 @@ namespace RubberduckTests.Refactoring
[TestFixture]
public class MoveCloserToUsageTests : RefactoringTestBase
{
[Test]
[Category("Refactorings")]
[Category("Move Closer")]
public void MoveCloserToUsageRefactoring_ModuleVariable_ClearsResidualNewLines()
{
//Input
const string inputCode =
@"Private bar As Boolean
Private Sub Foo()
bar = True
End Sub";
var selection = new Selection(1, 1);

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

var actualCode = RefactoredCode(inputCode, selection);
Assert.AreEqual(expectedCode, actualCode);
}

[Test]
[Category("Refactorings")]
[Category("Move Closer")]
public void MoveCloserToUsageRefactoring_LocalVariable_ClearsResidualNewLines()
{
//Input
const string inputCode =
@"Private Sub Foo()
Dim bar As Boolean
Dim var1 As Long
Dim var2 As String
bar = True
End Sub";
var selection = new Selection(2, 10);

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

var actualCode = RefactoredCode(inputCode, selection);
Assert.AreEqual(expectedCode, actualCode);
}

[Test]
[Category("Refactorings")]
[Category("Move Closer")]
Expand All @@ -25,6 +87,8 @@ public void MoveCloserToUsageRefactoring_Field()
//Input
const string inputCode =
@"Private bar As Boolean
Private Sub Foo()
bar = True
End Sub";
Expand Down Expand Up @@ -550,7 +614,6 @@ Debug.Print someParam
var selection = new Selection(2, 1);
const string expectedCode =
@"
Public Sub Test()
Dim foo As Long
SomeSub someParam:=foo
Expand Down Expand Up @@ -581,8 +644,8 @@ Debug.Print someParam

var selection = new Selection(1, 1);
const string expectedCode =
@"
Public Sub Test(): Dim foo As Long : SomeSub someParam:=foo: End Sub

@"Public Sub Test(): Dim foo As Long : SomeSub someParam:=foo: End Sub
Public Sub SomeSub(ByVal someParam As Long)
Debug.Print someParam
Expand Down Expand Up @@ -929,9 +992,7 @@ End Property

var selection = new Selection(1, 1);

const string expectedCode = @"
Public Sub Test()
const string expectedCode = @"Public Sub Test()
Debug.Print ""Some statements between""
Debug.Print ""Declaration and first usage!""
Dim foo As Class1
Expand Down

0 comments on commit ef1c9cc

Please sign in to comment.