Skip to content

Commit a257f18

Browse files
authored
Merge branch 'next' into 3246_InspectionEmptySelectCaseBlock
2 parents 0018170 + d7841e7 commit a257f18

File tree

2 files changed

+211
-7
lines changed

2 files changed

+211
-7
lines changed

Rubberduck.Parsing/Rewriter/RewriterInfo/VariableRewriterInfoFinder.cs

Lines changed: 39 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -24,8 +24,7 @@ private static RewriterInfo GetRewriterInfo(VBAParser.VariableSubStmtContext var
2424
var itemIndex = items.ToList().IndexOf(variable);
2525
var count = items.Count;
2626

27-
var element = context.Parent.Parent as VBAParser.ModuleDeclarationsElementContext;
28-
if (element != null)
27+
if (context.Parent.Parent is VBAParser.ModuleDeclarationsElementContext element)
2928
{
3029
return GetModuleVariableRemovalInfo(variable, element, count, itemIndex, items);
3130
}
@@ -60,15 +59,48 @@ private static RewriterInfo GetLocalVariableRemovalInfo(VBAParser.VariableSubStm
6059
{
6160
var mainBlockStmt = (VBAParser.MainBlockStmtContext)variables.Parent.Parent;
6261
var startIndex = mainBlockStmt.Start.TokenIndex;
63-
var blockStmt = (VBAParser.BlockStmtContext)mainBlockStmt.Parent;
64-
var block = (VBAParser.BlockContext)blockStmt.Parent;
65-
var statements = block.blockStmt();
66-
6762
if (count == 1)
6863
{
69-
var stopIndex = FindStopTokenIndex(statements, blockStmt, block);
64+
int stopIndex = variables.Stop.TokenIndex + 1; // also remove trailing newlines?
65+
66+
var containingBlock = (VBAParser.BlockContext)mainBlockStmt.Parent.Parent;
67+
var blockStmtIndex = containingBlock.children.IndexOf(mainBlockStmt.Parent);
68+
// a few things can happen here
69+
if (blockStmtIndex == containingBlock.ChildCount)
70+
{
71+
// well we're lucky?
72+
stopIndex = containingBlock.Stop.TokenIndex;
73+
}
74+
else if (containingBlock.GetChild(blockStmtIndex + 1) is VBAParser.EndOfStatementContext eos)
75+
{
76+
// since EOS includes the following comment, we need to do weird shit
77+
// eos cannot be EOF, since we're on a local var, but it can be a statment separator
78+
var eol = eos.endOfLine(0);
79+
if (eol?.commentOrAnnotation() != null)
80+
{
81+
stopIndex = eol.commentOrAnnotation().Start.TokenIndex - 1;
82+
}
83+
else
84+
{
85+
// remove until the end of the EOS or continue to the start of the following
86+
if (blockStmtIndex + 2 >= containingBlock.ChildCount)
87+
{
88+
stopIndex = eol.Stop.TokenIndex;
89+
}
90+
else
91+
{
92+
stopIndex = containingBlock.GetChild<ParserRuleContext>(blockStmtIndex + 2).Start.TokenIndex - 1;
93+
}
94+
}
95+
96+
}
97+
7098
return new RewriterInfo(startIndex, stopIndex);
7199
}
100+
101+
var blockStmt = (VBAParser.BlockStmtContext)mainBlockStmt.Parent;
102+
var block = (VBAParser.BlockContext)blockStmt.Parent;
103+
var statements = block.blockStmt();
72104
return GetRewriterInfoForTargetRemovedFromListStmt(target.Start, itemIndex, items);
73105
}
74106
}

RubberduckTests/QuickFixes/RemoveUnusedDeclarationQuickFixTests.cs

Lines changed: 172 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -142,5 +142,177 @@ Dim var1 As String
142142
}
143143

144144

145+
[TestMethod]
146+
[TestCategory("QuickFixes")]
147+
public void UnassignedVariable_WithFollowingEmptyLine_DoesNotRemoveEmptyLine()
148+
{
149+
const string inputCode =
150+
@"Sub Foo()
151+
Dim var1 As String
152+
153+
End Sub";
154+
155+
const string expectedCode =
156+
@"Sub Foo()
157+
158+
End Sub";
159+
160+
IVBComponent component;
161+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out component);
162+
var state = MockParser.CreateAndParse(vbe.Object);
163+
164+
var inspection = new VariableNotUsedInspection(state);
165+
new RemoveUnusedDeclarationQuickFix(state).Fix(inspection.GetInspectionResults().First());
166+
167+
var rewriter = state.GetRewriter(component);
168+
Assert.AreEqual(expectedCode, rewriter.GetText());
169+
}
170+
171+
[TestMethod]
172+
[TestCategory("QuickFixes")]
173+
public void UnassignedVariable_WithCommentOnSameLine_DoesNotRemoveComment()
174+
{
175+
const string inputCode =
176+
@"Sub Foo()
177+
Dim var1 As String ' Comment
178+
End Sub";
179+
180+
const string expectedCode =
181+
@"Sub Foo()
182+
' Comment
183+
End Sub";
184+
185+
IVBComponent component;
186+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out component);
187+
var state = MockParser.CreateAndParse(vbe.Object);
188+
189+
var inspection = new VariableNotUsedInspection(state);
190+
new RemoveUnusedDeclarationQuickFix(state).Fix(inspection.GetInspectionResults().First());
191+
192+
var rewriter = state.GetRewriter(component);
193+
Assert.AreEqual(expectedCode, rewriter.GetText());
194+
}
195+
196+
[TestMethod]
197+
[TestCategory("QuickFixes")]
198+
public void UnassignedVariable_WithCommentOnSameLineAndFollowingStuff_DoesNotRemoveComment()
199+
{
200+
const string inputCode =
201+
@"Function Foo() As String
202+
Dim var1 As String ' Comment
203+
Dim var2 As String
204+
var2 = ""Something""
205+
Foo = var2
206+
End Function";
207+
208+
const string expectedCode =
209+
@"Function Foo() As String
210+
' Comment
211+
Dim var2 As String
212+
var2 = ""Something""
213+
Foo = var2
214+
End Function";
215+
216+
IVBComponent component;
217+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out component);
218+
var state = MockParser.CreateAndParse(vbe.Object);
219+
220+
var inspection = new VariableNotUsedInspection(state);
221+
new RemoveUnusedDeclarationQuickFix(state).Fix(inspection.GetInspectionResults().First());
222+
223+
var rewriter = state.GetRewriter(component);
224+
Assert.AreEqual(expectedCode, rewriter.GetText());
225+
}
226+
227+
228+
229+
[TestMethod]
230+
[TestCategory("QuickFixes")]
231+
public void UnassignedVariable_WithFollowingCommentLine_DoesNotRemoveCommentLine()
232+
{
233+
const string inputCode =
234+
@"Sub Foo()
235+
Dim var1 As String
236+
' Comment
237+
End Sub";
238+
239+
const string expectedCode =
240+
@"Sub Foo()
241+
' Comment
242+
End Sub";
243+
244+
IVBComponent component;
245+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out component);
246+
var state = MockParser.CreateAndParse(vbe.Object);
247+
248+
var inspection = new VariableNotUsedInspection(state);
249+
new RemoveUnusedDeclarationQuickFix(state).Fix(inspection.GetInspectionResults().First());
250+
251+
var rewriter = state.GetRewriter(component);
252+
Assert.AreEqual(expectedCode, rewriter.GetText());
253+
}
254+
255+
[TestMethod]
256+
[TestCategory("QuickFixes")]
257+
public void UnassignedVariable_InMultideclaration_WithFollowingCommentLine_DoesNotRemoveCommentLineOrOtherDeclarations()
258+
{
259+
const string inputCode =
260+
@"Function Foo() As String
261+
Dim var1 As String, var2 As String
262+
' Comment
263+
var2 = ""Something""
264+
Foo = var2
265+
End Function";
266+
267+
const string expectedCode =
268+
@"Function Foo() As String
269+
Dim var2 As String
270+
' Comment
271+
var2 = ""Something""
272+
Foo = var2
273+
End Function";
274+
275+
IVBComponent component;
276+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out component);
277+
var state = MockParser.CreateAndParse(vbe.Object);
278+
279+
var inspection = new VariableNotUsedInspection(state);
280+
new RemoveUnusedDeclarationQuickFix(state).Fix(inspection.GetInspectionResults().First());
281+
282+
var rewriter = state.GetRewriter(component);
283+
Assert.AreEqual(expectedCode, rewriter.GetText());
284+
}
285+
286+
[TestMethod]
287+
[TestCategory("QuickFixes")]
288+
public void UnassignedVariable_InMultideclarationByStmtSeparators_WithFollowingCommentLine_DoesNotRemoveCommentLineOrOtherDeclarations()
289+
{
290+
const string inputCode =
291+
@"Function Foo() As String
292+
Dim var1 As String:Dim var2 As String
293+
' Comment
294+
var2 = ""Something""
295+
Foo = var2
296+
End Function";
297+
298+
const string expectedCode =
299+
@"Function Foo() As String
300+
Dim var2 As String
301+
' Comment
302+
var2 = ""Something""
303+
Foo = var2
304+
End Function";
305+
306+
IVBComponent component;
307+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out component);
308+
var state = MockParser.CreateAndParse(vbe.Object);
309+
310+
var inspection = new VariableNotUsedInspection(state);
311+
new RemoveUnusedDeclarationQuickFix(state).Fix(inspection.GetInspectionResults().First());
312+
313+
var rewriter = state.GetRewriter(component);
314+
Assert.AreEqual(expectedCode, rewriter.GetText());
315+
}
316+
145317
}
146318
}

0 commit comments

Comments
 (0)