Skip to content

Commit 5e91894

Browse files
authored
Merge pull request #3886 from BZngr/ParsingCrash_3883
Fixes StackOverflowException. TODO: Extract expression-evaluation logic into Rubberduck.Parsing and make it a resolver step to annotate all expressions with type info.
2 parents 025a90e + db6a72c commit 5e91894

File tree

3 files changed

+255
-43
lines changed

3 files changed

+255
-43
lines changed

Rubberduck.Inspections/Concrete/UnreachableCaseInspection/ParseTreeValueVisitor.cs

Lines changed: 33 additions & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -241,53 +241,50 @@ private bool TryGetLExprValue(VBAParser.LExprContext lExprContext, out string ex
241241
{
242242
expressionValue = string.Empty;
243243
declaredTypeName = string.Empty;
244-
var isMemberAccess = lExprContext.TryGetChildContext(out VBAParser.MemberAccessExprContext memberAccess);
245-
var isSimpleName = lExprContext.TryGetChildContext(out VBAParser.SimpleNameExprContext smplName);
246244

247-
if (!(isMemberAccess || isSimpleName))
245+
if (lExprContext.TryGetChildContext(out VBAParser.MemberAccessExprContext memberAccess))
248246
{
249-
return false;
247+
var member = memberAccess.GetChild<VBAParser.UnrestrictedIdentifierContext>();
248+
GetContextValue(member, out declaredTypeName, out expressionValue);
249+
return true;
250250
}
251251

252-
if (isMemberAccess)
252+
if (lExprContext.TryGetChildContext(out VBAParser.SimpleNameExprContext smplName))
253253
{
254-
var member = memberAccess.GetChild<VBAParser.UnrestrictedIdentifierContext>();
255-
256-
if (TryGetIdentifierReferenceForContext(member, out IdentifierReference idRef)
257-
&& idRef.Declaration.DeclarationType.HasFlag(DeclarationType.EnumerationMember)
258-
&& idRef.Declaration.Context is VBAParser.EnumerationStmt_ConstantContext)
259-
{
260-
var declaration = idRef.Declaration;
261-
var theCtxt = declaration.Context;
262-
expressionValue = GetConstantDeclarationValueToken(declaration);
263-
declaredTypeName = declaration.AsTypeIsBaseType ? declaration.AsTypeName : declaration.AsTypeDeclaration.AsTypeName;
264-
return true;
265-
}
254+
GetContextValue(smplName, out declaredTypeName, out expressionValue);
255+
return true;
266256
}
267-
else if (isSimpleName)
257+
258+
return false;
259+
}
260+
261+
private void GetContextValue(ParserRuleContext context, out string declaredTypeName, out string expressionValue)
262+
{
263+
expressionValue = context.GetText();
264+
declaredTypeName = string.Empty;
265+
266+
if (TryGetIdentifierReferenceForContext(context, out IdentifierReference rangeClauseIdentifierReference))
268267
{
269-
if (TryGetIdentifierReferenceForContext(smplName, out IdentifierReference rangeClauseIdentifierReference))
268+
var declaration = rangeClauseIdentifierReference.Declaration;
269+
expressionValue = rangeClauseIdentifierReference.IdentifierName;
270+
declaredTypeName = GetBaseTypeForDeclaration(declaration);
271+
272+
if (declaration.DeclarationType.HasFlag(DeclarationType.Constant)
273+
|| declaration.DeclarationType.HasFlag(DeclarationType.EnumerationMember))
270274
{
271-
var declaration = rangeClauseIdentifierReference.Declaration;
272-
if (declaration.DeclarationType.HasFlag(DeclarationType.Constant)
273-
|| declaration.DeclarationType.HasFlag(DeclarationType.EnumerationMember))
274-
{
275-
expressionValue = GetConstantDeclarationValueToken(declaration);
276-
declaredTypeName = declaration.AsTypeName;
277-
return true;
278-
}
275+
expressionValue = GetConstantDeclarationValueToken(declaration);
279276
}
280277
}
281-
return false;
282278
}
283279

284280
private bool TryGetIdentifierReferenceForContext(ParserRuleContext context, out IdentifierReference idRef)
285281
{
286282
idRef = null;
283+
var nameToMatch = context.GetText();
287284
var identifierReferences = (_state.DeclarationFinder.MatchName(context.GetText()).Select(dec => dec.References)).SelectMany(rf => rf);
288-
if (identifierReferences.Any())
285+
if (identifierReferences.Any(rf => rf.Context == context))
289286
{
290-
idRef = identifierReferences.First(rf => rf.Context == context);
287+
idRef = identifierReferences.First();
291288
return true;
292289
}
293290
return false;
@@ -319,13 +316,15 @@ private string GetConstantDeclarationValueToken(Declaration constantDeclaration)
319316
return string.Empty;
320317
}
321318

322-
private static string GetBaseTypeForDeclaration(Declaration declaration)
319+
private string GetBaseTypeForDeclaration(Declaration declaration)
323320
{
324-
if (!declaration.AsTypeIsBaseType)
321+
var localDeclaration = declaration;
322+
var iterationGuard = 0;
323+
while (!localDeclaration.AsTypeIsBaseType && iterationGuard++ < 5)
325324
{
326-
return GetBaseTypeForDeclaration(declaration.AsTypeDeclaration);
325+
localDeclaration = localDeclaration.AsTypeDeclaration;
327326
}
328-
return declaration.AsTypeName;
327+
return localDeclaration.AsTypeName;
329328
}
330329

331330
private static bool IsBinaryMathContext<T>(T context)

Rubberduck.Inspections/Concrete/UnreachableCaseInspection/SelectCaseStmtContextWrapper.cs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -124,6 +124,12 @@ private string DeriveTypeFromCaseClauses(IParseTreeVisitorResults inspValues, VB
124124
}
125125
}
126126

127+
if (TryDetermineEvaluationTypeFromTypes(caseClauseTypeNames, out _evalTypeName))
128+
{
129+
return _evalTypeName;
130+
}
131+
132+
caseClauseTypeNames.Remove(Tokens.Variant);
127133
if (TryDetermineEvaluationTypeFromTypes(caseClauseTypeNames, out _evalTypeName))
128134
{
129135
return _evalTypeName;
@@ -141,7 +147,7 @@ private static bool TryDetermineEvaluationTypeFromTypes(IEnumerable<string> type
141147
{
142148
return false;
143149
}
144-
typeList.All(tn => new string[] { typeList.First() }.Contains(tn));
150+
145151
//If all match, the typeName is easy...This is the only way to return "String" or "Currency".
146152
if (typeList.All(tn => new string[] { typeList.First() }.Contains(tn)))
147153
{

RubberduckTests/Inspections/UnreachableCaseInspectionTests.cs

Lines changed: 215 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using Rubberduck.Parsing;
55
using Rubberduck.Parsing.Grammar;
66
using Rubberduck.Parsing.Inspections.Resources;
7+
using Rubberduck.VBEditor.SafeComWrappers;
78
using RubberduckTests.Mocks;
89
using System;
910
using System.Collections.Generic;
@@ -362,12 +363,6 @@ public void UciUnit_LogicBinaryConstants(string operands, string expected)
362363
Assert.IsTrue(result.ParsesToConstantValue);
363364
}
364365

365-
// Dim A, B, C, D, MyCheck
366-
//A = 10: B = 8: C = 6: D = Null ' Initialize variables.
367-
//MyCheck = A > B Eqv B > C ' Returns True.
368-
//MyCheck = B > A Eqv B > C ' Returns False.
369-
//MyCheck = A > B Eqv B > D ' Returns Null.
370-
//MyCheck = A Eqv B ' Returns -3 (bitwise comparison).
371366
[TestCase("True_Eqv_True", "True")]
372367
[TestCase("False_Eqv_True", "False")]
373368
[TestCase("True_Eqv_False", "False")]
@@ -698,7 +693,7 @@ public void UciUnit_Extents(string typeName)
698693
* stored as variable RelationalOp expressions.
699694
*/
700695
[TestCase("Is < True", "Single=False")] //Always False
701-
[TestCase("Is <= True", "RelOp=Is <= True")] //Result depends on Select Case value
696+
[TestCase("Is <= True", "RelOp=Is <= True")]
702697
[TestCase("Is > True", "RelOp=Is > True")]
703698
[TestCase("Is >= True", "Single=True")] //Always True
704699
[TestCase("Is = True", "RelOp=Is = True")]
@@ -2247,7 +2242,205 @@ End Select
22472242
CheckActualResultsEqualsExpected(inputCode, unreachable: 1);
22482243
}
22492244

2245+
//Issue# 3885
2246+
//this test only proves that the Select Statement is not inspected
2247+
[Test]
2248+
[Category("Inspections")]
2249+
public void UciFunctional_BuiltInMember()
2250+
{
2251+
string inputCode =
2252+
@"
2253+
Option Explicit
2254+
2255+
Sub FooCount(x As Long)
2256+
2257+
Select Case err.Number
2258+
Case ""5903""
2259+
'OK
2260+
Case 5900 + 3
2261+
'Unreachable - but undetected by unit tests,
2262+
Case 5
2263+
'Unreachable - but undetected by unit tests,
2264+
Case 4 + 1
2265+
'Unreachable - but undetected by unit tests,
2266+
End Select
2267+
2268+
Select Case x
2269+
Case ""5""
2270+
MsgBox ""Foo""
2271+
Case 2 + 3
2272+
'Unreachable - just to make sure the test finds something
2273+
MsgBox ""Bar""
2274+
End Select
2275+
End Sub
2276+
";
2277+
2278+
CheckActualResultsEqualsExpected(inputCode, unreachable: 1);
2279+
}
2280+
2281+
[Test]
2282+
[Category("Inspections")]
2283+
public void UciFunctional_BuiltInMemberInCaseClause()
2284+
{
2285+
string inputCode =
2286+
@"
2287+
Option Explicit
2288+
2289+
Sub FooCount(x As Long)
2290+
2291+
Select Case x
2292+
Case 5900 + 3
2293+
'OK
2294+
Case err.Number
2295+
'OK - not evaluated
2296+
Case 5903
2297+
'Unreachable
2298+
Case 5900 + 2 + 1
2299+
'Unreachable
2300+
End Select
2301+
End Sub
2302+
";
2303+
2304+
CheckActualResultsEqualsExpected(inputCode, unreachable: 2);
2305+
}
2306+
2307+
//Issue# 3885 - replicates with UDT rather than a built-in
2308+
[TestCase("Long")]
2309+
[TestCase("Variant")]
2310+
[Category("Inspections")]
2311+
public void UciFunctional_MemberAccessor(string propertyType)
2312+
{
2313+
string inputCode =
2314+
@"
2315+
Option Explicit
2316+
2317+
Sub AddVariable(testClass As Class1)
2318+
Select Case testClass.AValue
2319+
Case 5903
2320+
'OK
2321+
Case 5900 + 3
2322+
'unreachable
2323+
Case Else
2324+
Exit Sub
2325+
End Select
2326+
End Sub";
2327+
2328+
string inputClassCode =
2329+
@"
2330+
Option Explicit
2331+
2332+
Private myVal As <propertyType>
2333+
2334+
Public Property Set AValue(val As <propertyType>)
2335+
myVal = val
2336+
End Property
2337+
2338+
Public Property Get AValue() As <propertyType>
2339+
AValue = myVal
2340+
End Property
2341+
";
2342+
inputClassCode = inputClassCode.Replace("<propertyType>", propertyType);
2343+
var components = new List<Tuple<string, string>>()
2344+
{
2345+
new Tuple<string, string>("TestModule1",inputCode),
2346+
new Tuple<string, string>("Class1", inputClassCode)
2347+
};
2348+
2349+
CheckActualResultsEqualsExpected(components, unreachable: 1);
2350+
}
2351+
2352+
[TestCase("Long")]
2353+
[TestCase("Variant")]
2354+
[Category("Inspections")]
2355+
public void UciFunctional_MemberAccessorInCaseClause(string propertyType)
2356+
{
2357+
string inputCode =
2358+
@"
2359+
Option Explicit
2360+
2361+
Sub AddVariable(x As Long)
2362+
Select Case x
2363+
Case 300
2364+
'OK
2365+
Case testClass.AValue
2366+
'OK - variable, not value
2367+
Case 150 + 150
2368+
'OK
2369+
Case 3 * 100
2370+
'OK
2371+
End Select
2372+
End Sub";
2373+
2374+
string inputClassCode =
2375+
@"
2376+
Option Explicit
2377+
2378+
Private myVal As <propertyType>
2379+
2380+
Public Property Set AValue(val As <propertyType>)
2381+
myVal = val
2382+
End Property
2383+
2384+
Public Property Get AValue() As <propertyType>
2385+
AValue = myVal
2386+
End Property
2387+
";
2388+
inputClassCode = inputClassCode.Replace("<propertyType>", propertyType);
2389+
var components = new List<Tuple<string, string>>()
2390+
{
2391+
new Tuple<string, string>("TestModule1",inputCode),
2392+
new Tuple<string, string>("Class1", inputClassCode)
2393+
};
2394+
2395+
CheckActualResultsEqualsExpected(components, unreachable: 2);
2396+
}
2397+
2398+
[TestCase("Long = 300")]
2399+
[Category("Inspections")]
2400+
public void UciFunctional_ConstanInOtherModule(string propertyType)
2401+
{
2402+
string inputCode =
2403+
@"
2404+
Option Explicit
2405+
2406+
Sub AddVariable(x As Variant)
2407+
Select Case x
2408+
Case TestModule2.My_CONSTANT
2409+
'OK
2410+
Case 300
2411+
'unreachable
2412+
Case Else
2413+
Exit Sub
2414+
End Select
2415+
End Sub";
2416+
2417+
string inputModule2Code =
2418+
@"
2419+
Option Explicit
2420+
2421+
Public Const MY_CONSTANT As <propertyTypeAndAssignment>
2422+
";
2423+
inputModule2Code = inputModule2Code.Replace("<propertyTypeAndAssignment>", propertyType);
2424+
var components = new List<Tuple<string, string>>()
2425+
{
2426+
new Tuple<string, string>("TestModule1",inputCode),
2427+
new Tuple<string, string>("TestModule2", inputModule2Code)
2428+
};
2429+
2430+
CheckActualResultsEqualsExpected(components, unreachable: 1);
2431+
}
2432+
22502433
private static void CheckActualResultsEqualsExpected(string inputCode, int unreachable = 0, int mismatch = 0, int caseElse = 0)
2434+
{
2435+
var components = new List<Tuple<string, string>>()
2436+
{
2437+
new Tuple<string, string>("TestModule1", inputCode)
2438+
};
2439+
2440+
CheckActualResultsEqualsExpected(components, unreachable, mismatch, caseElse);
2441+
}
2442+
2443+
private static void CheckActualResultsEqualsExpected(List<Tuple<string, string>> inputCode, int unreachable = 0, int mismatch = 0, int caseElse = 0)
22512444
{
22522445
var expected = new Dictionary<string, int>
22532446
{
@@ -2256,7 +2449,12 @@ private static void CheckActualResultsEqualsExpected(string inputCode, int unrea
22562449
{ InspectionsUI.UnreachableCaseInspection_CaseElse, caseElse },
22572450
};
22582451

2259-
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var _);
2452+
var builder = new MockVbeBuilder();
2453+
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected);
2454+
inputCode.ForEach(input => project.AddComponent(input.Item1, NameToComponentType(input.Item1), input.Item2));
2455+
builder = builder.AddProject(project.Build());
2456+
var vbe = builder.Build();
2457+
22602458
IEnumerable<Rubberduck.Parsing.Inspections.Abstract.IInspectionResult> actualResults;
22612459
using (var state = MockParser.CreateAndParse(vbe.Object))
22622460
{
@@ -2274,6 +2472,15 @@ private static void CheckActualResultsEqualsExpected(string inputCode, int unrea
22742472
Assert.AreEqual(expectedMsg, actualMsg);
22752473
}
22762474

2475+
private static ComponentType NameToComponentType(string name)
2476+
{
2477+
if (name.StartsWith("Class"))
2478+
{
2479+
return ComponentType.ClassModule;
2480+
}
2481+
return ComponentType.StandardModule;
2482+
}
2483+
22772484
private static string BuildResultString(int unreachableCount, int mismatchCount, int caseElseCount)
22782485
{
22792486
return $"Unreachable={unreachableCount}, Mismatch={mismatchCount}, CaseElse={caseElseCount}";

0 commit comments

Comments
 (0)