Skip to content

Commit e3680c0

Browse files
committed
Add declaration and newline removal methods
Extends the IModuleRewriter.Remove() method to clear residual blank lines between the removed declaration and the next declaration. Supports VariableDeclarations and ModuleBodyElementDeclarations removals. Also improves Variable declaration list handling.
1 parent 723bbac commit e3680c0

File tree

2 files changed

+288
-0
lines changed

2 files changed

+288
-0
lines changed
Lines changed: 101 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,101 @@
1+
using Antlr4.Runtime;
2+
using Rubberduck.Parsing;
3+
using Rubberduck.Parsing.Grammar;
4+
using Rubberduck.Parsing.Rewriter;
5+
using Rubberduck.Parsing.Symbols;
6+
using System;
7+
using System.Collections.Generic;
8+
using System.Linq;
9+
10+
namespace Rubberduck.Refactorings.Common
11+
{
12+
public static class IModuleRewriterExtensions
13+
{
14+
/// <summary>
15+
/// Removes variable declaration and subsequent <c>VBAParser.EndOfStatementContext</c>
16+
/// depending on the <paramref name="removeEndOfStmtContext"/> flag.
17+
/// This function is intended to be called only once per rewriter within a given <c>ModuleRewriteSession</c>.
18+
/// </summary>
19+
/// <remarks>
20+
/// Calling this function with <paramref name="removeEndOfStmtContext"/> defaulted to <c>true</c>
21+
/// avoids leaving residual newlines between the deleted declaration and the next declaration.
22+
/// The one-time call constraint is required for scenarios where variables to delete are declared in a list. Specifically,
23+
/// the use case where all the variables in the list are to be removed.
24+
/// If the variables to remove are not declared in a list, then this function can be called multiple times.
25+
/// </remarks>
26+
public static void RemoveVariables(this IModuleRewriter rewriter, IEnumerable<VariableDeclaration> toRemove, bool removeEndOfStmtContext = true)
27+
{
28+
if (!toRemove.Any()) { return; }
29+
30+
var fieldsByListContext = toRemove.Distinct()
31+
.GroupBy(f => f.Context.GetAncestor<VBAParser.VariableListStmtContext>());
32+
33+
foreach (var fieldsGroup in fieldsByListContext)
34+
{
35+
var variables = fieldsGroup.Key.children.Where(ch => ch is VBAParser.VariableSubStmtContext);
36+
if (variables.Count() == fieldsGroup.Count())
37+
{
38+
if (fieldsGroup.First().ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
39+
{
40+
rewriter.RemoveDeclaration<VBAParser.ModuleDeclarationsElementContext>(fieldsGroup.First(), removeEndOfStmtContext);
41+
}
42+
else
43+
{
44+
rewriter.RemoveDeclaration<VBAParser.BlockStmtContext>(fieldsGroup.First(), removeEndOfStmtContext);
45+
}
46+
continue;
47+
}
48+
49+
foreach (var target in fieldsGroup)
50+
{
51+
rewriter.Remove(target);
52+
}
53+
}
54+
}
55+
56+
/// <summary>
57+
/// Removes a member declaration and subsequent <c>VBAParser.EndOfStatementContext</c>
58+
/// depending on the <paramref name="removeEndOfStmtContext"/> flag.
59+
/// </summary>
60+
/// <remarks>
61+
/// Calling this function with <paramref name="removeEndOfStmtContext"/> defaulted to <c>true</c>
62+
/// avoids leaving residual newlines between the deleted declaration and the next declaration.
63+
/// </remarks>
64+
public static void RemoveMember(this IModuleRewriter rewriter, ModuleBodyElementDeclaration target, bool removeEndOfStmtContext = true)
65+
{
66+
RemoveMembers(rewriter, new ModuleBodyElementDeclaration[] { target }, removeEndOfStmtContext);
67+
}
68+
69+
/// <summary>
70+
/// Removes member declarations and subsequent <c>VBAParser.EndOfStatementContext</c>
71+
/// depending on the <paramref name="removeEndOfStmtContext"/> flag.
72+
/// </summary>
73+
/// <remarks>
74+
/// Calling this function with <paramref name="removeEndOfStmtContext"/> defaulted to <c>true</c>
75+
/// avoids leaving residual newlines between the deleted declaration and the next declaration.
76+
/// </remarks>
77+
public static void RemoveMembers(this IModuleRewriter rewriter, IEnumerable<ModuleBodyElementDeclaration> toRemove, bool removeEndOfStmtContext = true)
78+
{
79+
if (!toRemove.Any()) { return; }
80+
81+
foreach (var member in toRemove)
82+
{
83+
rewriter.RemoveDeclaration<VBAParser.ModuleBodyElementContext>(member, removeEndOfStmtContext);
84+
}
85+
}
86+
87+
private static void RemoveDeclaration<T>(this IModuleRewriter rewriter, Declaration declaration, bool removeEndOfStmtContext = true) where T : ParserRuleContext
88+
{
89+
if (!declaration.Context.TryGetAncestor<T>(out var elementContext))
90+
{
91+
throw new ArgumentException();
92+
}
93+
94+
rewriter.Remove(elementContext);
95+
if (removeEndOfStmtContext && elementContext.TryGetFollowingContext<VBAParser.EndOfStatementContext>(out var nextContext))
96+
{
97+
rewriter.Remove(nextContext);
98+
}
99+
}
100+
}
101+
}
Lines changed: 187 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,187 @@
1+
using NUnit.Framework;
2+
using Rubberduck.Parsing.Rewriter;
3+
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.Refactorings.Common;
6+
using RubberduckTests.Mocks;
7+
using System;
8+
using System.Collections.Generic;
9+
using System.Linq;
10+
11+
namespace RubberduckTests.Refactoring.EncapsulateField
12+
{
13+
[TestFixture]
14+
public class IModuleRewriterExtensionTests
15+
{
16+
private static string threeConsecutiveNewLines = $"{Environment.NewLine}{Environment.NewLine}{Environment.NewLine}";
17+
18+
[Test]
19+
[Category("Rewriter")]
20+
public void RemoveFieldDeclarations()
21+
{
22+
var inputCode =
23+
@"
24+
Option Explicit
25+
26+
Public mVar1 As Long
27+
28+
Public mVar2 As Long
29+
30+
Private mVar3 As String, mVar4 As Long, mVar5 As String
31+
32+
Private Type TestType
33+
FirstValue As Long
34+
SecondValue As Long
35+
End Type
36+
37+
Public Sub Test()
38+
End Sub";
39+
40+
var content = TestRemoveBlocks(inputCode, "mVar1", "mVar2", "mVar3", "mVar4", "mVar5");
41+
StringAssert.DoesNotContain(threeConsecutiveNewLines, content);
42+
}
43+
44+
[Test]
45+
[Category("Rewriter")]
46+
public void RemoveFieldDeclarationsUsesColonStmtDelimiter()
47+
{
48+
var inputCode =
49+
@"
50+
Option Explicit
51+
52+
Public mVar1 As Long: Public mVar2 As Long
53+
54+
Private mVar3 As String, mVar4 As Long, mVar5 As String
55+
56+
Private Type TestType
57+
FirstValue As Long
58+
SecondValue As Long
59+
End Type
60+
61+
Public Sub Test()
62+
End Sub";
63+
64+
var content = TestRemoveBlocks(inputCode, "mVar1", "mVar3", "mVar4", "mVar5");
65+
StringAssert.DoesNotContain(threeConsecutiveNewLines, content);
66+
StringAssert.DoesNotContain(":", content);
67+
}
68+
69+
[Test]
70+
[Category("Rewriter")]
71+
public void RemoveFieldDeclarations_LineContinuations()
72+
{
73+
var inputCode =
74+
@"
75+
Option Explicit
76+
77+
Public mVar1 As Long
78+
79+
Public mVar2 As Long
80+
81+
Private mVar3 As String _
82+
, mVar4 As Long _
83+
, mVar5 As String
84+
85+
Private Type TestType
86+
FirstValue As Long
87+
SecondValue As Long
88+
End Type
89+
90+
Public Sub Test()
91+
End Sub";
92+
93+
var content = TestRemoveBlocks(inputCode, "mVar1", "mVar2", "mVar3", "mVar5");
94+
StringAssert.DoesNotContain(threeConsecutiveNewLines, content);
95+
}
96+
97+
[Test]
98+
[Category("Rewriter")]
99+
public void RemoveFieldDeclarations_RemovesAllBlankLines()
100+
{
101+
var inputCode =
102+
@"
103+
Option Explicit
104+
Public mVar1 As Long
105+
106+
107+
108+
109+
110+
Public mVar2 As Long
111+
Private mVar3 As String, mVar4 As Long, mVar5 As String
112+
113+
114+
115+
116+
117+
Private Type TestType
118+
FirstValue As Long
119+
SecondValue As Long
120+
End Type
121+
122+
Public Sub Test()
123+
End Sub";
124+
125+
var content = TestRemoveBlocks(inputCode, "mVar1", "mVar2", "mVar3", "mVar4", "mVar5");
126+
StringAssert.DoesNotContain(threeConsecutiveNewLines, content);
127+
}
128+
129+
[Test]
130+
[Category("Rewriter")]
131+
public void RemoveMemberDeclarations()
132+
{
133+
var inputCode =
134+
@"
135+
Option Explicit
136+
137+
Public mVar1 As Long
138+
139+
Private Type TestType
140+
FirstValue As Long
141+
SecondValue As Long
142+
End Type
143+
144+
Public Sub Test1()
145+
End Sub
146+
147+
Public Sub Test2()
148+
End Sub
149+
150+
151+
Public Sub Test3()
152+
End Sub
153+
154+
Public Sub Test4()
155+
End Sub
156+
";
157+
158+
var content = TestRemoveBlocks(inputCode, "Test2", "Test3");
159+
StringAssert.DoesNotContain(threeConsecutiveNewLines, content);
160+
}
161+
162+
private string TestRemoveBlocks(string inputCode, params string[] identifiers)
163+
{
164+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
165+
(RubberduckParserState state, IRewritingManager rewriteManager) = MockParser.CreateAndParseWithRewritingManager(vbe.Object);
166+
using (state)
167+
{
168+
var targets = new List<Declaration>();
169+
foreach (var id in identifiers)
170+
{
171+
var target = state.DeclarationFinder
172+
.MatchName(id).Single();
173+
targets.Add(target);
174+
}
175+
176+
var qmn = targets.First().QualifiedModuleName;
177+
var rewriteSession = rewriteManager.CheckOutCodePaneSession();
178+
var rewriter = rewriteSession.CheckOutModuleRewriter(qmn);
179+
180+
rewriter.RemoveVariables(targets.OfType<VariableDeclaration>());
181+
rewriter.RemoveMembers(targets.OfType<ModuleBodyElementDeclaration>());
182+
183+
return rewriter.GetText();
184+
}
185+
}
186+
}
187+
}

0 commit comments

Comments
 (0)