Skip to content

Commit ae09406

Browse files
authored
Merge pull request #6027 from BZngr/5907HandleConcatOpContext
Add ConcatOpContext handling to the ImplicitTypeToExplicitRefactoringAction
2 parents 1bb58c3 + 54dd27b commit ae09406

6 files changed

+487
-7
lines changed
Lines changed: 148 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,148 @@
1+
using Antlr4.Runtime;
2+
using Rubberduck.Parsing;
3+
using Rubberduck.Parsing.Grammar;
4+
using Rubberduck.Parsing.Symbols;
5+
using Rubberduck.Parsing.VBA;
6+
using System;
7+
using System.Collections.Generic;
8+
using System.Linq;
9+
using System.Text;
10+
using System.Threading.Tasks;
11+
12+
namespace Rubberduck.Refactorings.ImplicitTypeToExplicit
13+
{
14+
/// <summary>
15+
/// ConcatOpContextResolver resolves the AsTypeName of ConcatOpContext expressions
16+
/// assumed to be on the RHS of a Variable, Constant, or Parameter assignment.
17+
/// </summary>
18+
public class ConcatOpContextResolver
19+
{
20+
private readonly IDeclarationFinderProvider _declarationFinderProvider;
21+
22+
public ConcatOpContextResolver(IDeclarationFinderProvider declarationFinderProvider)
23+
{
24+
_declarationFinderProvider = declarationFinderProvider;
25+
}
26+
/// <summary>
27+
/// Returns an AsTypeName result of 'String' or 'Variant' for a List of
28+
/// ConcatOpContext expressions.
29+
/// </summary>
30+
/// <remarks>
31+
/// Until a unified Expression engine is available, the default AsTypeName,
32+
/// 'Variant', is returned for all ConcatOpContexts that contain operand
33+
/// contexts other than LiteralExprContexts and LExprContexts.
34+
///
35+
/// In general, the '&amp;' operator (and this function) returns 'String'
36+
/// unless a 'Variant' operand is found within the expression.
37+
/// </remarks>
38+
public List<string> InferAsTypeNames(IEnumerable<VBAParser.ConcatOpContext> tContexts)
39+
{
40+
if (!tContexts.Any())
41+
{
42+
return new List<string>();
43+
}
44+
45+
var operandContexts = GetConcatOperandContexts(tContexts).ToList();
46+
47+
//The logic below will incorrectly interpret a (very unlikely) statement
48+
//like '5 & Null & Null & 5' as a 'Variant' instead of the correct
49+
//AsTypename 'String' ("55").
50+
//TODO: The issue above can be resolved once a unified Expression engine
51+
//is available,
52+
if (tContexts.Any(ctxt => ctxt.GetText().Contains("Null & Null")))
53+
{
54+
return new List<string>() { Tokens.Variant };
55+
}
56+
57+
var literals = operandContexts.OfType<VBAParser.LiteralExprContext>();
58+
var lexprs = operandContexts.OfType<VBAParser.LExprContext>();
59+
if (operandContexts.Count() != (literals.Count() + lexprs.Count()))
60+
{
61+
//A context type other than VBAParser.LiteralExprContext
62+
//or VBAParser.LExprContext is used - resort to the default AsTypeName
63+
return new List<string>() { Tokens.Variant };
64+
}
65+
66+
if (InferAsTypeNamesForLExprContexts(lexprs, _declarationFinderProvider)
67+
.Any(tn => tn == Tokens.Variant))
68+
{
69+
return new List<string>() { Tokens.Variant };
70+
}
71+
72+
return new List<string>() { Tokens.String };
73+
}
74+
75+
private static IEnumerable<ParserRuleContext> GetConcatOperandContexts(
76+
IEnumerable<VBAParser.ConcatOpContext> tContexts)
77+
{
78+
var results = new List<ParserRuleContext>();
79+
foreach (var ctxt in tContexts)
80+
{
81+
results = ExtractOperands(ctxt, results);
82+
}
83+
84+
return results;
85+
}
86+
87+
private static List<ParserRuleContext> ExtractOperands(
88+
VBAParser.ConcatOpContext concatOpContext,
89+
List<ParserRuleContext> operandContexts)
90+
{
91+
if (concatOpContext.children.First() is VBAParser.ConcatOpContext concatOpCtxt)
92+
{
93+
operandContexts = ExtractOperands(concatOpCtxt, operandContexts);
94+
}
95+
96+
var operands = new List<ParserRuleContext>
97+
{ concatOpContext.children.First() as ParserRuleContext,
98+
concatOpContext.children.Last() as ParserRuleContext};
99+
100+
foreach (var operandContext in operands)
101+
{
102+
if (!(operandContext is VBAParser.ConcatOpContext))
103+
{
104+
operandContexts.Add(operandContext);
105+
}
106+
}
107+
108+
return operandContexts;
109+
}
110+
private static List<string> InferAsTypeNamesForLExprContexts(
111+
IEnumerable<VBAParser.LExprContext> lExprCtxts,
112+
IDeclarationFinderProvider declarationFinderProvider)
113+
{
114+
var results = new List<string>();
115+
116+
string typeNameResult;
117+
foreach (var lExpr in lExprCtxts)
118+
{
119+
var target = GetLExprDeclaration(lExpr, declarationFinderProvider);
120+
typeNameResult = target.IsObject ? Tokens.Variant : target.AsTypeName;
121+
results.Add(typeNameResult);
122+
}
123+
return results;
124+
}
125+
126+
private static Declaration GetLExprDeclaration(
127+
VBAParser.LExprContext lExprContext,
128+
IDeclarationFinderProvider declarationFinderProvider)
129+
{
130+
var simpleNameExpression =
131+
lExprContext.GetDescendent<VBAParser.SimpleNameExprContext>();
132+
133+
var candidates = declarationFinderProvider.DeclarationFinder
134+
.MatchName(simpleNameExpression.GetText());
135+
136+
if (candidates.Count() == 1)
137+
{
138+
return candidates.First();
139+
}
140+
141+
var lExprDeclaration = candidates
142+
.Single(c => c.References.Any(rf => rf.Context is ParserRuleContext prc
143+
&& simpleNameExpression.Equals(prc)));
144+
145+
return lExprDeclaration;
146+
}
147+
}
148+
}

Rubberduck.Refactorings/ImplicitTypeToExplicit/ImplicitAsTypeNameResolver.cs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ internal class ImplicitAsTypeNameResolver
1313
{
1414
private readonly LiteralExprContextToAsTypeNameConverter _literalExprContextEvaluator;
1515
private readonly IDeclarationFinderProvider _declarationFinderProvider;
16+
private readonly ConcatOpContextResolver _concatOpContextResolver;
1617
private readonly Declaration _target;
1718

1819
public ImplicitAsTypeNameResolver(IDeclarationFinderProvider declarationFinderProvider,
@@ -21,6 +22,8 @@ public ImplicitAsTypeNameResolver(IDeclarationFinderProvider declarationFinderPr
2122
_declarationFinderProvider = declarationFinderProvider;
2223
_literalExprContextEvaluator = new LiteralExprContextToAsTypeNameConverter(parseTreeValueFactory);
2324
_target = target;
25+
26+
_concatOpContextResolver = new ConcatOpContextResolver(declarationFinderProvider);
2427
}
2528

2629
public List<string> InferAsTypeNames(IReadOnlyCollection<VBAParser.LiteralExprContext> tContexts)
@@ -29,6 +32,11 @@ public List<string> InferAsTypeNames(IReadOnlyCollection<VBAParser.LiteralExprCo
2932
public List<string> InferAsTypeNames(IReadOnlyCollection<VBAParser.NewExprContext> tContexts)
3033
=> tContexts.Select(c => c.GetChild<VBAParser.LExprContext>()?.GetText() ?? string.Empty).ToList();
3134

35+
public List<string> InferAsTypeNames(IReadOnlyCollection<VBAParser.ConcatOpContext> tContexts)
36+
{
37+
return _concatOpContextResolver.InferAsTypeNames(tContexts);
38+
}
39+
3240
public List<string> InferAsTypeNames(IReadOnlyCollection<VBAParser.LetStmtContext> tContexts)
3341
{
3442
var functionAsTypeNames = new List<string>();

Rubberduck.Refactorings/ImplicitTypeToExplicit/ImplicitTypeToExplicitRefactoringAction.cs

Lines changed: 19 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -101,8 +101,9 @@ private static void InferTypeNamesFromDeclarationWithDefaultValue(ParserRuleCont
101101

102102
var lExprContext = context.GetChild<VBAParser.LExprContext>();
103103
var litExprContext = context.GetChild<VBAParser.LiteralExprContext>();
104+
var concatExprContext = context.GetChild<VBAParser.ConcatOpContext>();
104105

105-
if (lExprContext is null && litExprContext is null)
106+
if (lExprContext is null && litExprContext is null && concatExprContext is null)
106107
{
107108
//Declarations that have a default value expression (Constants and Optional parameters)
108109
//must resolve to an AsTypeName. Expressions are indeterminant and result assigning the Variant type
@@ -119,6 +120,11 @@ private static void InferTypeNamesFromDeclarationWithDefaultValue(ParserRuleCont
119120
{
120121
resultsHandler.AddCandidates(nameof(VBAParser.LiteralExprContext), resolver.InferAsTypeNames(new List<VBAParser.LiteralExprContext>() { litExprContext }));
121122
}
123+
124+
if (concatExprContext != null)
125+
{
126+
resultsHandler.AddCandidates(nameof(VBAParser.ConcatOpContext), resolver.InferAsTypeNames(new List<VBAParser.ConcatOpContext>() { concatExprContext }));
127+
}
122128
}
123129

124130
private static void InferTypeNamesFromAssignmentLHSUsage(Declaration target, ImplicitAsTypeNameResolver resolver, AsTypeNamesResultsHandler resultsHandler)
@@ -138,21 +144,29 @@ List<T> AssignmentRHSContexts<T>() where T: ParserRuleContext
138144

139145
//Until a unified Expression engine is available, the following are the only ParserRuleContext
140146
//Subclasses that are evaluated.
141-
var newExprContexts = AssignmentRHSContexts<VBAParser.NewExprContext>();
142-
var lExprContexts = AssignmentRHSContexts<VBAParser.LExprContext>();
143-
var litExprContexts = AssignmentRHSContexts<VBAParser.LiteralExprContext>();
147+
var newExprContexts = AssignmentRHSContexts<VBAParser.NewExprContext>().ToList();
148+
var lExprContexts = AssignmentRHSContexts<VBAParser.LExprContext>().ToList();
149+
var litExprContexts = AssignmentRHSContexts<VBAParser.LiteralExprContext>().ToList();
150+
var concatExprContexts = AssignmentRHSContexts<VBAParser.ConcatOpContext>().ToList();
144151

145-
if (assignmentContextsToEvaluate.Count() == newExprContexts.Count + lExprContexts.Count + litExprContexts.Count)
152+
var countOfAllContexts = SumContextCounts<VBAParser.ExpressionContext>(
153+
newExprContexts, lExprContexts, litExprContexts, concatExprContexts);
154+
155+
if (assignmentContextsToEvaluate.Count() == countOfAllContexts)
146156
{
147157
resultsHandler.AddCandidates(nameof(VBAParser.NewExprContext), resolver.InferAsTypeNames(newExprContexts));
148158
resultsHandler.AddCandidates(nameof(VBAParser.LExprContext), resolver.InferAsTypeNames(lExprContexts));
149159
resultsHandler.AddCandidates(nameof(VBAParser.LiteralExprContext), resolver.InferAsTypeNames(litExprContexts));
160+
resultsHandler.AddCandidates(nameof(VBAParser.ConcatOpContext), resolver.InferAsTypeNames(concatExprContexts));
150161
return;
151162
}
152163

153164
resultsHandler.AddIndeterminantResult();
154165
}
155166

167+
private static long SumContextCounts<T>(params IEnumerable<T>[] contextLists) where T : VBAParser.ExpressionContext
168+
=> contextLists.Sum(c => c.Count());
169+
156170
private static void InferTypeNamesFromAssignmentRHSUsage(Declaration target, ImplicitAsTypeNameResolver resolver, AsTypeNamesResultsHandler resultsHandler)
157171
{
158172
var rhsLetStmtContexts = target.References

RubberduckTests/Refactoring/ImplicitTypeToExplicit/ImplicitTypeToExplicitRefactoringActionConstantTests.cs

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -157,6 +157,24 @@ public void ConstantTypedByFunctionType(string procedureType, string getToken)
157157
Public {procedureType} {getToken}AValue() As Double
158158
AValue = MY_CONSTANT
159159
End {procedureType}
160+
";
161+
var refactoredCode = RefactoredCode(inputCode, NameAndDeclarationTypeTuple(targetName));
162+
StringAssert.Contains($"{targetName} As {expectedType}", refactoredCode);
163+
}
164+
165+
[TestCase("5 & 5", "String")]
166+
[TestCase("Null & Null", "Variant")]
167+
[TestCase(@"Null & ""Test""", "String")]
168+
[TestCase("5 & Null", "String")]
169+
[Category("Refactorings")]
170+
[Category(nameof(ImplicitTypeToExplicitRefactoringAction))]
171+
public void ConstantTypedByConcatOp(string expression, string expectedType)
172+
{
173+
var targetName = "MY_CONSTANT";
174+
var inputCode =
175+
$@"
176+
Public Const MY_CONSTANT = {expression}
177+
160178
";
161179
var refactoredCode = RefactoredCode(inputCode, NameAndDeclarationTypeTuple(targetName));
162180
StringAssert.Contains($"{targetName} As {expectedType}", refactoredCode);

RubberduckTests/Refactoring/ImplicitTypeToExplicit/ImplicitTypeToExplicitRefactoringActionParameterTests.cs

Lines changed: 35 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -249,6 +249,41 @@ public void Parameter_Arrays(string argList, string expectedArgList)
249249
StringAssert.Contains(expectedArgList, refactoredCode);
250250
}
251251

252+
[TestCase("5 & 5", "String")]
253+
[TestCase("Null & Null", "Variant")]
254+
[TestCase(@"Null & ""Test""", "String")]
255+
[TestCase(@"5 & Null", "String")]
256+
[Category("Refactorings")]
257+
[Category(nameof(ImplicitTypeToExplicitRefactoringAction))]
258+
public void ParameterWithDefaultValue_ConcatExpression(string expression, string expected)
259+
{
260+
var targetName = "fizz";
261+
var inputCode =
262+
$@"
263+
Sub Test(Optional ByVal fizz = {expression})
264+
End Sub";
265+
266+
var refactoredCode = RefactoredCode(inputCode, NameAndDeclarationTypeTuple(targetName));
267+
StringAssert.Contains($"{targetName} As {expected}", refactoredCode);
268+
}
269+
270+
[Test]
271+
[Category("Refactorings")]
272+
[Category(nameof(ImplicitTypeToExplicitRefactoringAction))]
273+
public void ParameterAssignedWithinProcedure_ConcatExpression()
274+
{
275+
var targetName = "fizz";
276+
var expectedType = "String";
277+
var inputCode =
278+
@"
279+
Sub Test(ByVal countSuffix As Long, fizz)
280+
fizz = ""Test"" & countSuffix
281+
End Sub";
282+
283+
var refactoredCode = RefactoredCode(inputCode, NameAndDeclarationTypeTuple(targetName));
284+
StringAssert.Contains($"{targetName} As {expectedType}", refactoredCode);
285+
}
286+
252287
(string, DeclarationType) NameAndDeclarationTypeTuple(string name)
253288
=> (name, DeclarationType.Parameter);
254289
}

0 commit comments

Comments
 (0)