Skip to content

Commit f2f190b

Browse files
committed
Adds unit test for 4659 and 4680
1 parent d256eaf commit f2f190b

File tree

2 files changed

+149
-17
lines changed

2 files changed

+149
-17
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection/UnreachableCaseInspection.cs

Lines changed: 17 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -51,13 +51,11 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5151
var qualifiedSelectCaseStmts = Listener.Contexts
5252
.Where(result => !IsIgnoringInspectionResultFor(result.ModuleName, result.Context.Start.Line));
5353

54-
var listener = (UnreachableCaseInspectionListener)Listener;
55-
var parseTreeValueVisitor = CreateParseTreeValueVisitor(_valueFactory, listener.EnumerationStmtContexts.ToList(), GetIdentifierReferenceForContext);
56-
parseTreeValueVisitor.OnValueResultCreated += ValueResults.OnNewValueResult;
54+
ParseTreeValueVisitor.OnValueResultCreated += ValueResults.OnNewValueResult;
5755

5856
foreach (var qualifiedSelectCaseStmt in qualifiedSelectCaseStmts)
5957
{
60-
qualifiedSelectCaseStmt.Context.Accept(parseTreeValueVisitor);
58+
qualifiedSelectCaseStmt.Context.Accept(ParseTreeValueVisitor);
6159
var selectCaseInspector = _unreachableCaseInspectorFactory.Create((VBAParser.SelectCaseStmtContext)qualifiedSelectCaseStmt.Context, ValueResults, _valueFactory, GetVariableTypeName);
6260

6361
selectCaseInspector.InspectForUnreachableCases();
@@ -71,6 +69,20 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
7169
return _inspectionResults;
7270
}
7371

72+
private IParseTreeValueVisitor _parseTreeValueVisitor;
73+
public IParseTreeValueVisitor ParseTreeValueVisitor
74+
{
75+
get
76+
{
77+
if (_parseTreeValueVisitor is null)
78+
{
79+
var listener = (UnreachableCaseInspectionListener)Listener;
80+
_parseTreeValueVisitor = CreateParseTreeValueVisitor(_valueFactory, listener.EnumerationStmtContexts.ToList(), GetIdentifierReferenceForContext);
81+
}
82+
return _parseTreeValueVisitor;
83+
}
84+
}
85+
7486
private void CreateInspectionResult(QualifiedContext<ParserRuleContext> selectStmt, ParserRuleContext unreachableBlock, string message)
7587
{
7688
var result = new QualifiedContextInspectionResult(this,
@@ -80,9 +92,7 @@ private void CreateInspectionResult(QualifiedContext<ParserRuleContext> selectSt
8092
}
8193

8294
public static IParseTreeValueVisitor CreateParseTreeValueVisitor(IParseTreeValueFactory valueFactory, List<VBAParser.EnumerationStmtContext> allEnums, Func<ParserRuleContext, (bool success, IdentifierReference idRef)> func)
83-
{
84-
return new ParseTreeValueVisitor(valueFactory, allEnums, func);
85-
}
95+
=> new ParseTreeValueVisitor(valueFactory, allEnums, func);
8696

8797
//Method is used as a delegate to avoid propogating RubberduckParserState beyond this class
8898
private (bool success, IdentifierReference idRef) GetIdentifierReferenceForContext(ParserRuleContext context)

RubberduckTests/Inspections/UnreachableCase/UnreachableCaseInspectionTests.cs

Lines changed: 132 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -3,8 +3,10 @@
33
using Rubberduck.Inspections.Concrete.UnreachableCaseInspection;
44
using Rubberduck.Parsing;
55
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.Parsing.Symbols;
67
using Rubberduck.Resources.Inspections;
78
using Rubberduck.VBEditor.SafeComWrappers;
9+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
810
using RubberduckTests.Mocks;
911
using System.Collections.Generic;
1012
using System.Linq;
@@ -1357,10 +1359,10 @@ End Select
13571359
Assert.AreEqual(expectedMsg, actualMsg);
13581360
}
13591361

1360-
//#4119
1362+
//https://github.com/rubberduck-vba/Rubberduck/issues/4119
13611363
[Test]
13621364
[Category("Inspections")]
1363-
public void UnreachableCaseInspection_EnumerationIssue4119Scenario()
1365+
public void UnreachableCaseInspection_Enumeration()
13641366
{
13651367
const string inputCode =
13661368
@"
@@ -1801,7 +1803,6 @@ End Select
18011803
Assert.AreEqual(expectedMsg, actualMsg);
18021804
}
18031805

1804-
//Issue# 3885
18051806
//this test only proves that the Select Statement is not inspected
18061807
[Test]
18071808
[Category("Inspections")]
@@ -1861,7 +1862,6 @@ End Select
18611862
Assert.AreEqual(expectedMsg, actualMsg);
18621863
}
18631864

1864-
//Issue# 3885 - replicates with UDT rather than a built-in
18651865
[TestCase("Long")]
18661866
[TestCase("Variant")]
18671867
[Category("Inspections")]
@@ -2258,7 +2258,7 @@ End Select
22582258
Assert.AreEqual(expectedMsg, actualMsg);
22592259
}
22602260

2261-
//From Issue #3962
2261+
//https://github.com/rubberduck-vba/Rubberduck/issues/3962
22622262
[Test]
22632263
[Category("Inspections")]
22642264
public void UnreachableCaseInspection_AdditionString()
@@ -2441,13 +2441,127 @@ End Sub
24412441
Assert.AreEqual(expectedMsg, actualMsg);
24422442
}
24432443

2444+
[TestCase("vbBack", "\b")]
2445+
[TestCase("vbCrLf", "\r\n")]
2446+
[TestCase("vbCr", "\r")]
2447+
[TestCase("vbLf", "\n")]
2448+
[TestCase("vbFormFeed", "\f")]
2449+
[TestCase("vbNewLine", "\r\n")]
2450+
[TestCase("vbNullChar", "\0")]
2451+
[TestCase("vbNullString", null)]
2452+
[TestCase("vbTab", "\t")]
2453+
[TestCase("vbVerticalTab", "\v")]
2454+
[Category("Inspections")]
2455+
public void UnreachableCaseInspection_VbStringConstantToLiteral_AreEqual(string constToken, string expected)
2456+
{
2457+
var parseTreeValueVisitor = new ParseTreeValueVisitor(null, new List<VBAParser.EnumerationStmtContext>(), null) as ITestParseTreeVisitor;
2458+
if (parseTreeValueVisitor.IsVBStringConstantToLiteral(constToken, out string literalValue))
2459+
{
2460+
Assert.AreEqual(expected, literalValue);
2461+
return;
2462+
}
2463+
Assert.Fail($"TryConvertVBStringConstantToLiteral failed to convert {constToken}");
2464+
}
2465+
2466+
[TestCase("\r", true)]
2467+
[TestCase("\r\n", true)]
2468+
[TestCase("\b", true)]
2469+
[TestCase("\f", true)]
2470+
[TestCase("\0", true)]
2471+
[TestCase("\t", true)]
2472+
[TestCase("\v", true)]
2473+
[TestCase(null, false)]
2474+
[Category("Inspections")]
2475+
public void UnreachableCaseInspection_ControlCharToLiteral_AreEqual(string constToken, bool expected)
2476+
{
2477+
var parseTreeValueVisitor = new ParseTreeValueVisitor(null, new List<VBAParser.EnumerationStmtContext>(), null) as ITestParseTreeVisitor;
2478+
Assert.AreEqual(expected, parseTreeValueVisitor.IsNonPrintingControlCharacter(constToken));
2479+
}
2480+
2481+
//https://github.com/rubberduck-vba/Rubberduck/issues/4659
2482+
[Test]
2483+
[Category("Inspections")]
2484+
public void UnreachableCaseInspection_VbObjectErrorConstant()
2485+
{
2486+
var expectedUnreachableCount = 2;
2487+
string inputCode =
2488+
@"
2489+
Enum Fubar
2490+
Foo = vbObjectError + 1
2491+
Bar = vbObjectError + 2
2492+
End Enum
2493+
2494+
Sub Example(value As Long)
2495+
Select Case value
2496+
Case Fubar.Foo
2497+
Debug.Print ""Foo""
2498+
Case Fubar.Bar
2499+
Debug.Print ""Bar""
2500+
Case vbObjectError + 1 'unreachable
2501+
Debug.Print ""Unreachable""
2502+
Case -2147221502 'unreachable
2503+
Debug.Print ""Unreachable""
2504+
End Select
2505+
End Sub
2506+
";
2507+
(bool IsType, string ExpressionValue, string TypeName) TestGetValuedDeclaration(Declaration declaration)
2508+
{
2509+
if (declaration.IdentifierName.Equals("vbObjectError"))
2510+
{
2511+
return (true, "-2147221504", Tokens.Long);
2512+
}
2513+
return (false, null, null);
2514+
}
2515+
2516+
var vbe = CreateStandardModuleProject(inputCode);
2517+
2518+
IEnumerable<Rubberduck.Parsing.Inspections.Abstract.IInspectionResult> actualResults;
2519+
using (var state = MockParser.CreateAndParse(vbe.Object))
2520+
{
2521+
var inspection = new UnreachableCaseInspection(state);
2522+
var parseTreeValueVisitor = inspection.ParseTreeValueVisitor as ITestParseTreeVisitor;
2523+
2524+
parseTreeValueVisitor.InjectValuedDeclarationEvaluator(TestGetValuedDeclaration);
2525+
2526+
var inspector = InspectionsHelper.GetInspector(inspection);
2527+
actualResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
2528+
}
2529+
2530+
var actualUnreachable = actualResults.Where(ar => ar.Description.Equals(InspectionResults.UnreachableCaseInspection_Unreachable));
2531+
2532+
Assert.AreEqual(expectedUnreachableCount, actualUnreachable.Count());
2533+
}
2534+
2535+
//https://github.com/rubberduck-vba/Rubberduck/issues/4680
2536+
[Test]
2537+
[Ignore("Issue 4680")]
2538+
[Category("Inspections")]
2539+
public void UnreachableCaseInspection_VbStringConstant()
2540+
{
2541+
string inputCode =
2542+
@"
2543+
Sub Foo(value As String)
2544+
Select Case value
2545+
Case ""Hello"" + vbNewLine + ""World""
2546+
MsgBox ""vbNewLine version""
2547+
Case ""Hello"" + vbCr + vbLf + ""World"" 'unreachable
2548+
MsgBox ""vbCr + vbLf version""
2549+
Case ""Reachable""
2550+
MsgBox ""Reachable""
2551+
End Select
2552+
End Sub
2553+
";
2554+
(string expectedMsg, string actualMsg) = CheckActualResultsEqualsExpected(inputCode, unreachable: 1);
2555+
Assert.AreEqual(expectedMsg, actualMsg);
2556+
}
2557+
24442558
private static (string expectedMsg, string actualMsg) CheckActualResultsEqualsExpected(string inputCode, int unreachable = 0, int mismatch = 0, int caseElse = 0, int inherentlyUnreachable = 0, int overflow = 0)
24452559
{
24462560
var components = new List<(string moduleName, string inputCode)>() { ("TestModule1", inputCode) };
24472561
return CheckActualResultsEqualsExpected(components, unreachable, mismatch, caseElse, inherentlyUnreachable, overflow);
24482562
}
24492563

2450-
private static (string expectedMsg, string actualMsg) CheckActualResultsEqualsExpected(List<(string moduleName, string inputBlock)> inputCode, int unreachable = 0, int mismatch = 0, int caseElse = 0, int inherentlyUnreachable = 0, int overflow = 0)
2564+
private static (string expectedMsg, string actualMsg) CheckActualResultsEqualsExpected(List<(string moduleName, string inputCode)> components, int unreachable = 0, int mismatch = 0, int caseElse = 0, int inherentlyUnreachable = 0, int overflow = 0)
24512565
{
24522566
var expected = new Dictionary<string, int>
24532567
{
@@ -2458,10 +2572,7 @@ private static (string expectedMsg, string actualMsg) CheckActualResultsEqualsEx
24582572
{ InspectionResults.UnreachableCaseInspection_CaseElse, caseElse },
24592573
};
24602574

2461-
var builder = new MockVbeBuilder();
2462-
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected);
2463-
inputCode.ForEach(input => project.AddComponent(input.moduleName, NameToComponentType(input.moduleName), input.inputBlock));
2464-
var vbe = builder.AddProject(project.Build()).Build();
2575+
var vbe = CreateStandardModuleProject(components);
24652576

24662577
IEnumerable<Rubberduck.Parsing.Inspections.Abstract.IInspectionResult> actualResults;
24672578
using (var state = MockParser.CreateAndParse(vbe.Object))
@@ -2486,6 +2597,17 @@ private static (string expectedMsg, string actualMsg) CheckActualResultsEqualsEx
24862597
return (expectedMsg, actualMsg);
24872598
}
24882599

2600+
private Moq.Mock<IVBE> CreateStandardModuleProject(string inputCode)
2601+
=> CreateStandardModuleProject(new List<(string moduleName, string inputCode)>() { ("TestModule1", inputCode) });
2602+
2603+
private static Moq.Mock<IVBE> CreateStandardModuleProject(List<(string moduleName, string inputCode)> components)
2604+
{
2605+
var builder = new MockVbeBuilder();
2606+
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected);
2607+
components.ForEach(input => project.AddComponent(input.moduleName, NameToComponentType(input.moduleName), input.inputCode));
2608+
return builder.AddProject(project.Build()).Build();
2609+
}
2610+
24892611
private static ComponentType NameToComponentType(string name)
24902612
=> name.StartsWith("Class") ? ComponentType.ClassModule : ComponentType.StandardModule;
24912613

0 commit comments

Comments
 (0)