Skip to content

Commit 8ed40be

Browse files
authored
Merge pull request #4218 from MDoerner/FixIntroduceLocalVariable
Fix introduce local variable
2 parents 21612f8 + 9727d38 commit 8ed40be

17 files changed

+1564
-96
lines changed

Rubberduck.CodeAnalysis/QuickFixes/IntroduceLocalVariableQuickFix.cs

Lines changed: 57 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,9 @@
11
using System;
2+
using System.Text.RegularExpressions;
23
using Rubberduck.Inspections.Abstract;
34
using Rubberduck.Inspections.Concrete;
5+
using Rubberduck.Parsing;
6+
using Rubberduck.Parsing.Grammar;
47
using Rubberduck.Parsing.Inspections.Abstract;
58
using Rubberduck.Parsing.VBA;
69

@@ -22,8 +25,60 @@ public IntroduceLocalVariableQuickFix(RubberduckParserState state)
2225

2326
public override void Fix(IInspectionResult result)
2427
{
25-
var instruction = $"{Environment.NewLine}Dim {result.Target.IdentifierName} As Variant{Environment.NewLine}";
26-
_state.GetRewriter(result.Target).InsertBefore(result.Target.Context.Start.TokenIndex, instruction);
28+
var identifierContext = result.Target.Context;
29+
var enclosingStatmentContext = identifierContext.GetAncestor<VBAParser.BlockStmtContext>();
30+
var instruction = IdentifierDeclarationText(result.Target.IdentifierName, EndOfStatementText(enclosingStatmentContext), FrontPadding(enclosingStatmentContext));
31+
_state.GetRewriter(result.Target).InsertBefore(enclosingStatmentContext.Start.TokenIndex, instruction);
32+
}
33+
34+
private string EndOfStatementText(VBAParser.BlockStmtContext context)
35+
{
36+
if (!context.TryGetPrecedingContext<VBAParser.IndividualNonEOFEndOfStatementContext>(out var individualEndOfStmtContext))
37+
{
38+
return Environment.NewLine;
39+
}
40+
41+
var endOfLine = individualEndOfStmtContext.endOfLine();
42+
43+
if (endOfLine?.commentOrAnnotation() == null)
44+
{
45+
return individualEndOfStmtContext.GetText();
46+
}
47+
48+
//There is a comment inside the preceding endOfLine, which we do not want to duplicate.
49+
var whitespaceContext = individualEndOfStmtContext.whiteSpace(0);
50+
return Environment.NewLine + (whitespaceContext?.GetText() ?? string.Empty);
51+
}
52+
53+
private string FrontPadding(VBAParser.BlockStmtContext context)
54+
{
55+
var statementLabelContext = context.statementLabelDefinition();
56+
if (statementLabelContext == null)
57+
{
58+
return string.Empty;
59+
}
60+
61+
var statementLabelTextAsWhitespace = ReplaceNonWhitespaceWithSpace(statementLabelContext.GetText());
62+
var whitespaceContext = context.whiteSpace();
63+
return statementLabelTextAsWhitespace + (whitespaceContext?.GetText() ?? string.Empty);
64+
}
65+
66+
private string ReplaceNonWhitespaceWithSpace(string input)
67+
{
68+
if (input == null || input.Equals(string.Empty))
69+
{
70+
return string.Empty;
71+
}
72+
73+
var pattern = @"[^\r\n\t ]";
74+
var replacement = " ";
75+
var regex = new Regex(pattern);
76+
return regex.Replace(input, replacement);
77+
}
78+
79+
private string IdentifierDeclarationText(string identifierName, string endOfStatementText, string prefix)
80+
{
81+
return $"{prefix}Dim {identifierName} As Variant{endOfStatementText}";
2782
}
2883

2984
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.IntroduceLocalVariableQuickFix;

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 9 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -895,10 +895,16 @@ endOfLine :
895895
| whiteSpace? commentOrAnnotation
896896
;
897897

898-
// we expect endOfStatement to consume all trailing whitespace
898+
// We expect endOfStatement to consume all trailing whitespace blank statements.
899+
// We have to special case the end of file since infiniftly mant EOF tokens can be consumed at the end of file.
899900
endOfStatement :
900-
(endOfLine whiteSpace? | (whiteSpace? COLON whiteSpace?))+
901-
| whiteSpace? EOF
901+
individualNonEOFEndOfStatement+ | whiteSpace? EOF
902+
;
903+
904+
// we expect endOfStatement to consume all trailing whitespace
905+
individualNonEOFEndOfStatement :
906+
endOfLine whiteSpace?
907+
| whiteSpace? COLON whiteSpace?
902908
;
903909

904910
// Annotations must come before comments because of precedence. ANTLR4 matches as much as possible then chooses the one that comes first.

Rubberduck.Parsing/ParserRuleContextExtensions.cs

Lines changed: 125 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -144,13 +144,51 @@ private static TContext GetAncestor_Recursive<TContext>(ParserRuleContext contex
144144
return GetAncestor_Recursive<TContext>((ParserRuleContext)context.Parent);
145145
}
146146

147+
/// <summary>
148+
/// Returns the context's first ancestor containing the token with the specified token index or the context itels if it already contains the token.
149+
/// </summary>
150+
public static ParserRuleContext GetAncestorContainingTokenIndex(this ParserRuleContext context, int tokenIndex)
151+
{
152+
if (context == null)
153+
{
154+
return default;
155+
}
156+
157+
if (context.ContainsTokenIndex(tokenIndex))
158+
{
159+
return context;
160+
}
161+
162+
var parent = context.Parent as ParserRuleContext;
163+
164+
if (parent == null)
165+
{
166+
return default;
167+
}
168+
169+
return GetAncestorContainingTokenIndex(parent, tokenIndex);
170+
}
171+
172+
/// <summary>
173+
/// Determines whether the context contains the token with the specified token index.
174+
/// </summary>
175+
public static bool ContainsTokenIndex(this ParserRuleContext context, int tokenIndex)
176+
{
177+
if (context == null)
178+
{
179+
return false;
180+
}
181+
182+
return context.Start.TokenIndex <= tokenIndex && tokenIndex <= context.Stop.TokenIndex;
183+
}
184+
147185
/// <summary>
148186
/// Returns the context's first descendent of the generic Type.
149187
/// </summary>
150188
public static TContext GetDescendent<TContext>(this ParserRuleContext context) where TContext : ParserRuleContext
151189
{
152190
var descendents = GetDescendents<TContext>(context);
153-
return descendents.Any() ? descendents.First() : null;
191+
return descendents.FirstOrDefault();
154192
}
155193

156194
/// <summary>
@@ -173,15 +211,99 @@ public static bool TryGetChildContext<TContext>(this ParserRuleContext ctxt, out
173211
return opCtxt != null;
174212
}
175213

214+
/// <summary>
215+
/// Returns the context's first descendent of the generic type containing the token with the specified token index.
216+
/// </summary>
217+
public static TContext GetDescendentContainingTokenIndex<TContext>(this ParserRuleContext context, int tokenIndex) where TContext : ParserRuleContext
218+
{
219+
var descendents = GetDescendentsContainingTokenIndex<TContext>(context, tokenIndex);
220+
return descendents.FirstOrDefault();
221+
}
222+
223+
/// <summary>
224+
/// Returns all the context's descendents of the generic type containing the token with the specified token index.
225+
/// If there are multiple matches, they are ordered from outermost to innermost context.
226+
/// </summary>
227+
public static IEnumerable<TContext> GetDescendentsContainingTokenIndex<TContext>(this ParserRuleContext context, int tokenIndex) where TContext : ParserRuleContext
228+
{
229+
if (!context.ContainsTokenIndex(tokenIndex))
230+
{
231+
return new List<TContext>();
232+
}
233+
234+
var matches = new List<TContext>();
235+
if (context is TContext match)
236+
{
237+
matches.Add(match);
238+
}
239+
240+
foreach (var child in context.children)
241+
{
242+
if (child is ParserRuleContext childContext && childContext.ContainsTokenIndex(tokenIndex))
243+
{
244+
matches.AddRange(childContext.GetDescendentsContainingTokenIndex<TContext>(tokenIndex));
245+
break; //Only one child can contain the token index.
246+
}
247+
}
248+
249+
return matches;
250+
}
251+
252+
/// <summary>
253+
/// Returns the context containing the token preceding the context provided it is of the specified generic type.
254+
/// </summary>
255+
public static bool TryGetPrecedingContext<TContext>(this ParserRuleContext context, out TContext precedingContext) where TContext : ParserRuleContext
256+
{
257+
precedingContext = null;
258+
if (context == null)
259+
{
260+
return false;
261+
}
262+
263+
var precedingTokenIndex = context.Start.TokenIndex - 1;
264+
var ancestorContainingPrecedingIndex = context.GetAncestorContainingTokenIndex(precedingTokenIndex);
265+
266+
if (ancestorContainingPrecedingIndex == null)
267+
{
268+
return false;
269+
}
270+
271+
precedingContext = ancestorContainingPrecedingIndex.GetDescendentContainingTokenIndex<TContext>(precedingTokenIndex);
272+
return precedingContext != null;
273+
}
274+
275+
/// <summary>
276+
/// Returns the context containing the token following the context provided it is of the specified generic type.
277+
/// </summary>
278+
public static bool TryGetFollowingContext<TContext>(this ParserRuleContext context, out TContext followingContext) where TContext : ParserRuleContext
279+
{
280+
followingContext = null;
281+
if (context == null)
282+
{
283+
return false;
284+
}
285+
286+
var followingTokenIndex = context.Stop.TokenIndex + 1;
287+
var ancestorContainingFollowingIndex = context.GetAncestorContainingTokenIndex(followingTokenIndex);
288+
289+
if (ancestorContainingFollowingIndex == null)
290+
{
291+
return false;
292+
}
293+
294+
followingContext = ancestorContainingFollowingIndex.GetDescendentContainingTokenIndex<TContext>(followingTokenIndex);
295+
return followingContext != null;
296+
}
297+
298+
176299
private class ChildNodeListener<TContext> : VBAParserBaseListener where TContext : ParserRuleContext
177300
{
178301
private readonly HashSet<TContext> _matches = new HashSet<TContext>();
179302
public IEnumerable<TContext> Matches => _matches;
180303

181304
public override void EnterEveryRule(ParserRuleContext context)
182305
{
183-
var match = context as TContext;
184-
if (match != null)
306+
if (context is TContext match)
185307
{
186308
_matches.Add(match);
187309
}

Rubberduck.Parsing/Rewriter/RewriterInfo/ConstantRewriterInfoFinder.cs

Lines changed: 19 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -37,34 +37,39 @@ private static RewriterInfo GetModuleConstantRemovalInfo(
3737
VBAParser.ConstSubStmtContext target, VBAParser.ModuleDeclarationsElementContext element,
3838
int count, int itemIndex, IReadOnlyList<VBAParser.ConstSubStmtContext> items)
3939
{
40-
var startIndex = element.Start.TokenIndex;
41-
var parent = (VBAParser.ModuleDeclarationsContext)element.Parent;
42-
var elements = parent.moduleDeclarationsElement();
43-
4440
if (count == 1)
4541
{
46-
var stopIndex = FindStopTokenIndex(elements, element, parent);
47-
return new RewriterInfo(startIndex, stopIndex);
42+
return GetSeparateModuleConstantRemovalInfo(element);
4843
}
4944
return GetRewriterInfoForTargetRemovedFromListStmt(target.Start, itemIndex, items);
5045
}
5146

47+
private static RewriterInfo GetSeparateModuleConstantRemovalInfo(VBAParser.ModuleDeclarationsElementContext element)
48+
{
49+
var startIndex = element.Start.TokenIndex;
50+
var stopIndex = FindStopTokenIndexForRemoval(element);
51+
return new RewriterInfo(startIndex, stopIndex);
52+
}
53+
5254
private static RewriterInfo GetLocalConstantRemovalInfo(VBAParser.ConstSubStmtContext target,
5355
VBAParser.ConstStmtContext constants,
5456
int count, int itemIndex, IReadOnlyList<VBAParser.ConstSubStmtContext> items)
5557
{
56-
var mainBlockStmt = (VBAParser.MainBlockStmtContext)constants.Parent;
57-
var startIndex = mainBlockStmt.Start.TokenIndex;
58-
var blockStmt = (VBAParser.BlockStmtContext)mainBlockStmt.Parent;
59-
var block = (VBAParser.BlockContext)blockStmt.Parent;
60-
var statements = block.blockStmt();
61-
6258
if (count == 1)
6359
{
64-
var stopIndex = FindStopTokenIndex(statements, mainBlockStmt, block);
65-
return new RewriterInfo(startIndex, stopIndex);
60+
return GetSeparateLocalConstantRemovalInfo(constants);
6661
}
6762
return GetRewriterInfoForTargetRemovedFromListStmt(target.Start, itemIndex, items);
6863
}
64+
65+
private static RewriterInfo GetSeparateLocalConstantRemovalInfo(VBAParser.ConstStmtContext constStmtContext)
66+
{
67+
var mainBlockStmt = constStmtContext.GetAncestor<VBAParser.MainBlockStmtContext>();
68+
var startIndex = mainBlockStmt.Start.TokenIndex;
69+
70+
var stopIndex = FindStopTokenIndexForRemoval(mainBlockStmt);
71+
72+
return new RewriterInfo(startIndex, stopIndex);
73+
}
6974
}
7075
}

Rubberduck.Parsing/Rewriter/RewriterInfo/RewriterInfoFinderBase.cs

Lines changed: 51 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -21,36 +21,67 @@ protected static RewriterInfo GetRewriterInfoForTargetRemovedFromListStmt(IToken
2121
return new RewriterInfo(startIndex, stopIndex);
2222
}
2323

24-
protected static int FindStopTokenIndex<TParent>(IReadOnlyList<ParserRuleContext> items, ParserRuleContext item, TParent parent)
24+
protected static int FindStopTokenIndexForRemoval(VBAParser.ModuleDeclarationsElementContext element)
2525
{
26-
for (var i = 0; i < items.Count; i++)
26+
if (!element.TryGetFollowingContext<VBAParser.IndividualNonEOFEndOfStatementContext>(out var followingIndividualEndOfLineStatement))
2727
{
28-
if (items[i] != item)
29-
{
30-
continue;
31-
}
32-
return FindStopTokenIndex((dynamic)parent, i);
28+
return element.Stop.TokenIndex;
3329
}
3430

35-
return item.Stop.TokenIndex;
31+
//If the endOfStatement starts with a statement separator, it is safe to simply remove that.
32+
if (followingIndividualEndOfLineStatement.COLON() != null)
33+
{
34+
return followingIndividualEndOfLineStatement.Stop.TokenIndex;
35+
}
36+
37+
//Since there is no statement separator, the individual endOfStatement must contain an endOfLine.
38+
var endOfLine = followingIndividualEndOfLineStatement.endOfLine();
39+
40+
//EndOfLines contain preceding comments. So, we cannot remove the line, if there is one.
41+
if (endOfLine.commentOrAnnotation() != null)
42+
{
43+
return endOfLine.commentOrAnnotation().Start.TokenIndex - 1;
44+
}
45+
46+
return followingIndividualEndOfLineStatement.Stop.TokenIndex;
47+
}
48+
49+
protected static int FindStopTokenIndexForRemoval(VBAParser.MainBlockStmtContext mainBlockStmt)
50+
{
51+
return FindStopTokenIndexForRemoval((VBAParser.BlockStmtContext)mainBlockStmt.Parent);
3652
}
3753

38-
protected static int FindStopTokenIndex(IReadOnlyList<VBAParser.BlockStmtContext> blockStmts, VBAParser.MainBlockStmtContext mainBlockStmt, VBAParser.BlockContext block)
54+
//This overload differs from the one for module declaration elements because we have to take care that we do not invalidate line labels or line numbers on the next line.
55+
protected static int FindStopTokenIndexForRemoval(VBAParser.BlockStmtContext blockStmt)
3956
{
40-
for (var i = 0; i < blockStmts.Count; i++)
57+
if (!blockStmt.TryGetFollowingContext<VBAParser.IndividualNonEOFEndOfStatementContext>(out var followingIndividualEndOfLineStatement))
4158
{
42-
if (blockStmts[i].mainBlockStmt() != mainBlockStmt)
43-
{
44-
continue;
45-
}
46-
if (blockStmts[i].statementLabelDefinition() != null)
47-
{
48-
return mainBlockStmt.Stop.TokenIndex; //Removing the following endOfStatement if there is a label on the line would break the code.
49-
}
50-
return FindStopTokenIndex(block, i);
59+
return blockStmt.Stop.TokenIndex;
5160
}
5261

53-
return mainBlockStmt.Stop.TokenIndex;
62+
//If the endOfStatement starts with a statement separator, it is safe to simply remove that.
63+
if (followingIndividualEndOfLineStatement.COLON() != null)
64+
{
65+
return followingIndividualEndOfLineStatement.Stop.TokenIndex;
66+
}
67+
68+
//Since there is no statement separator, the individual endOfStatement must contain an endOfLine.
69+
var endOfLine = followingIndividualEndOfLineStatement.endOfLine();
70+
71+
//EndOfLines contain preceding comments. So, we cannot remove the line, if there is one.
72+
if (endOfLine.commentOrAnnotation() != null)
73+
{
74+
return endOfLine.commentOrAnnotation().Start.TokenIndex - 1;
75+
}
76+
77+
//There could be a statement label right after the individual endOfStatement.
78+
//In that case, removing the endOfStatement would break the code.
79+
if (followingIndividualEndOfLineStatement.TryGetFollowingContext<VBAParser.StatementLabelDefinitionContext>(out _))
80+
{
81+
return blockStmt.Stop.TokenIndex;
82+
}
83+
84+
return followingIndividualEndOfLineStatement.Stop.TokenIndex;
5485
}
5586

5687
private static int FindStopTokenIndex(VBAParser.BlockContext context, int index)

0 commit comments

Comments
 (0)