Skip to content

Commit 71b4693

Browse files
committed
Modified to use InsepectionTestsBase
1 parent a960c30 commit 71b4693

File tree

1 file changed

+41
-52
lines changed

1 file changed

+41
-52
lines changed

RubberduckTests/Inspections/UnreachableCase/UnreachableCaseInspectionTests.cs

Lines changed: 41 additions & 52 deletions
Original file line numberDiff line numberDiff line change
@@ -3,8 +3,9 @@
33
using Rubberduck.Inspections.Concrete.UnreachableCaseInspection;
44
using Rubberduck.Parsing;
55
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.Parsing.Inspections.Abstract;
67
using Rubberduck.Parsing.Symbols;
7-
using Rubberduck.Resources.Inspections;
8+
using Rubberduck.Parsing.VBA;
89
using Rubberduck.VBEditor.SafeComWrappers;
910
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1011
using RubberduckTests.Mocks;
@@ -15,7 +16,7 @@
1516
namespace RubberduckTests.Inspections.UnreachableCase
1617
{
1718
[TestFixture]
18-
public class UnreachableCaseInspectionTests
19+
public class UnreachableCaseInspectionTests : InspectionTestsBase
1920
{
2021
private IUnreachableCaseInspectionFactoryProvider _factoryProvider;
2122

@@ -1896,10 +1897,10 @@ Public Property Get AValue() As {propertyType}
18961897
AValue = myVal
18971898
End Property
18981899
";
1899-
var components = new List<(string moduleName, string inputCode)>()
1900+
var components = new List<(string moduleName, string inputCode, ComponentType componentType)>()
19001901
{
1901-
("TestModule1", inputCode),
1902-
("Class1", inputClassCode)
1902+
("TestModule1", inputCode, ComponentType.StandardModule),
1903+
("Class1", inputClassCode, ComponentType.ClassModule)
19031904
};
19041905

19051906
(string expectedMsg, string actualMsg) = CheckActualResultsEqualsExpected(components, unreachable: 1);
@@ -1942,10 +1943,10 @@ Public Property Get AValue() As {propertyType}
19421943
AValue = myVal
19431944
End Property
19441945
";
1945-
var components = new List<(string moduleName, string inputCode)>()
1946+
var components = new List<(string moduleName, string inputCode, ComponentType componentType)>()
19461947
{
1947-
("TestModule1",inputCode),
1948-
("Class1", inputClassCode)
1948+
("TestModule1",inputCode, ComponentType.StandardModule),
1949+
("Class1", inputClassCode, ComponentType.ClassModule)
19491950
};
19501951

19511952
(string expectedMsg, string actualMsg) = CheckActualResultsEqualsExpected(components, unreachable: 2);
@@ -1977,10 +1978,10 @@ Option Explicit
19771978
19781979
Public Const MY_CONSTANT As {propertyType}
19791980
";
1980-
var components = new List<(string moduleName, string inputCode)>()
1981+
var components = new List<(string moduleName, string inputCode, ComponentType componentType)>()
19811982
{
1982-
("TestModule1",inputCode),
1983-
("TestModule2", inputModule2Code)
1983+
("TestModule1",inputCode, ComponentType.StandardModule),
1984+
("TestModule2", inputModule2Code, ComponentType.StandardModule)
19841985
};
19851986

19861987
(string expectedMsg, string actualMsg) = CheckActualResultsEqualsExpected(components, unreachable: 1);
@@ -2469,7 +2470,7 @@ End Sub
24692470

24702471
var vbe = CreateStandardModuleProject(inputCode);
24712472

2472-
IEnumerable<Rubberduck.Parsing.Inspections.Abstract.IInspectionResult> actualResults;
2473+
var actualResults = Enumerable.Empty<IInspectionResult>();
24732474
using (var state = MockParser.CreateAndParse(vbe.Object))
24742475
{
24752476
var inspection = new UnreachableCaseInspection(state);
@@ -2481,7 +2482,7 @@ End Sub
24812482
actualResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
24822483
}
24832484

2484-
var actualUnreachable = actualResults.Where(ar => ar.Description.Equals(InspectionResults.UnreachableCaseInspection_Unreachable));
2485+
var actualUnreachable = actualResults.Where(ar => ar.Description.Equals(Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_Unreachable));
24852486

24862487
Assert.AreEqual(expectedUnreachableCount, actualUnreachable.Count());
24872488
}
@@ -2523,7 +2524,7 @@ End Sub
25232524
";
25242525
var vbe = CreateStandardModuleProject(inputCode);
25252526

2526-
IEnumerable<Rubberduck.Parsing.Inspections.Abstract.IInspectionResult> actualResults;
2527+
var actualResults = Enumerable.Empty<IInspectionResult>();
25272528
using (var state = MockParser.CreateAndParse(vbe.Object))
25282529
{
25292530
var inspection = new UnreachableCaseInspection(state);
@@ -2535,7 +2536,7 @@ End Sub
25352536
actualResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
25362537
}
25372538

2538-
var actualUnreachable = actualResults.Where(ar => ar.Description.Equals(InspectionResults.UnreachableCaseInspection_Unreachable));
2539+
var actualUnreachable = actualResults.Where(ar => ar.Description.Equals(Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_Unreachable));
25392540

25402541
Assert.AreEqual(expectedUnreachableCount, actualUnreachable.Count());
25412542
}
@@ -2564,61 +2565,44 @@ private static (bool IsType, string ExpressionValue, string TypeName) TestGetVal
25642565
return (true, expressionValue , typename);
25652566
}
25662567

2567-
private static (string expectedMsg, string actualMsg) CheckActualResultsEqualsExpected(string inputCode, int unreachable = 0, int mismatch = 0, int caseElse = 0, int inherentlyUnreachable = 0, int overflow = 0)
2568+
private (string expectedMsg, string actualMsg) CheckActualResultsEqualsExpected(string inputCode, int unreachable = 0, int mismatch = 0, int caseElse = 0, int inherentlyUnreachable = 0, int overflow = 0)
25682569
{
2569-
var components = new List<(string moduleName, string inputCode)>() { ("TestModule1", inputCode) };
2570+
var components = new List<(string moduleName, string inputCode, ComponentType componentType)>() { ("TestModule1", inputCode, ComponentType.StandardModule) };
25702571
return CheckActualResultsEqualsExpected(components, unreachable, mismatch, caseElse, inherentlyUnreachable, overflow);
25712572
}
25722573

2573-
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)
2574+
private (string expectedMsg, string actualMsg) CheckActualResultsEqualsExpected(List<(string moduleName, string inputCode, ComponentType componentType)> components, int unreachable = 0, int mismatch = 0, int caseElse = 0, int inherentlyUnreachable = 0, int overflow = 0)
25742575
{
25752576
var expected = new Dictionary<string, int>
25762577
{
2577-
{ InspectionResults.UnreachableCaseInspection_Unreachable, unreachable },
2578-
{ InspectionResults.UnreachableCaseInspection_InherentlyUnreachable, inherentlyUnreachable },
2579-
{ InspectionResults.UnreachableCaseInspection_TypeMismatch, mismatch },
2580-
{ InspectionResults.UnreachableCaseInspection_Overflow, overflow },
2581-
{ InspectionResults.UnreachableCaseInspection_CaseElse, caseElse },
2578+
{ Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_Unreachable, unreachable },
2579+
{ Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_InherentlyUnreachable, inherentlyUnreachable },
2580+
{ Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_TypeMismatch, mismatch },
2581+
{ Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_Overflow, overflow },
2582+
{ Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_CaseElse, caseElse },
25822583
};
25832584

2584-
var vbe = CreateStandardModuleProject(components);
2585+
var actualResults = InspectionResultsForModules(components);
25852586

2586-
IEnumerable<Rubberduck.Parsing.Inspections.Abstract.IInspectionResult> actualResults;
2587-
using (var state = MockParser.CreateAndParse(vbe.Object))
2588-
{
2589-
var inspector = InspectionsHelper.GetInspector(new UnreachableCaseInspection(state));
2590-
actualResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
2591-
}
2592-
var actualUnreachable = actualResults.Where(ar => ar.Description.Equals(InspectionResults.UnreachableCaseInspection_Unreachable));
2593-
var actualMismatches = actualResults.Where(ar => ar.Description.Equals(InspectionResults.UnreachableCaseInspection_TypeMismatch));
2594-
var actualUnreachableCaseElses = actualResults.Where(ar => ar.Description.Equals(InspectionResults.UnreachableCaseInspection_CaseElse));
2595-
var actualInherentUnreachable = actualResults.Where(ar => ar.Description.Equals(InspectionResults.UnreachableCaseInspection_InherentlyUnreachable));
2596-
var actualOverflow = actualResults.Where(ar => ar.Description.Equals(InspectionResults.UnreachableCaseInspection_Overflow));
2587+
var actualUnreachable = actualResults.Where(ar => ar.Description.Equals(Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_Unreachable));
2588+
var actualMismatches = actualResults.Where(ar => ar.Description.Equals(Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_TypeMismatch));
2589+
var actualUnreachableCaseElses = actualResults.Where(ar => ar.Description.Equals(Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_CaseElse));
2590+
var actualInherentUnreachable = actualResults.Where(ar => ar.Description.Equals(Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_InherentlyUnreachable));
2591+
var actualOverflow = actualResults.Where(ar => ar.Description.Equals(Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_Overflow));
25972592

25982593
var actualMsg = BuildResultString(actualUnreachable.Count(), actualMismatches.Count(), actualUnreachableCaseElses.Count(), actualInherentUnreachable.Count(), actualOverflow.Count());
2599-
var expectedMsg = BuildResultString(expected[InspectionResults.UnreachableCaseInspection_Unreachable],
2600-
expected[InspectionResults.UnreachableCaseInspection_TypeMismatch],
2601-
expected[InspectionResults.UnreachableCaseInspection_CaseElse],
2602-
expected[InspectionResults.UnreachableCaseInspection_InherentlyUnreachable],
2603-
expected[InspectionResults.UnreachableCaseInspection_Overflow]
2594+
var expectedMsg = BuildResultString(expected[Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_Unreachable],
2595+
expected[Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_TypeMismatch],
2596+
expected[Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_CaseElse],
2597+
expected[Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_InherentlyUnreachable],
2598+
expected[Rubberduck.Resources.Inspections.InspectionResults.UnreachableCaseInspection_Overflow]
26042599
);
26052600

26062601
return (expectedMsg, actualMsg);
26072602
}
26082603

26092604
private Moq.Mock<IVBE> CreateStandardModuleProject(string inputCode)
2610-
=> CreateStandardModuleProject(new List<(string moduleName, string inputCode)>() { ("TestModule1", inputCode) });
2611-
2612-
private static Moq.Mock<IVBE> CreateStandardModuleProject(List<(string moduleName, string inputCode)> components)
2613-
{
2614-
var builder = new MockVbeBuilder();
2615-
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected);
2616-
components.ForEach(input => project.AddComponent(input.moduleName, NameToComponentType(input.moduleName), input.inputCode));
2617-
return builder.AddProject(project.Build()).Build();
2618-
}
2619-
2620-
private static ComponentType NameToComponentType(string name)
2621-
=> name.StartsWith("Class") ? ComponentType.ClassModule : ComponentType.StandardModule;
2605+
=> MockVbeBuilder.BuildFromModules(new List<(string moduleName, string inputCode, ComponentType componentType)>() { ("TestModule1", inputCode, ComponentType.StandardModule) });
26222606

26232607
private static string BuildResultString(int unreachableCount, int mismatchCount, int caseElseCount, int inherentCount, int overflowCount)
26242608
=> $"Unreachable={unreachableCount}, Mismatch={mismatchCount}, CaseElse={caseElseCount}, Inherent={inherentCount}, Overflow={overflowCount}";
@@ -2649,5 +2633,10 @@ private IParseTreeVisitorResults GetParseTreeValueResults(string inputCode, out
26492633
}
26502634
return valueResults;
26512635
}
2636+
2637+
protected override IInspection InspectionUnderTest(RubberduckParserState state)
2638+
{
2639+
return new UnreachableCaseInspection(state);
2640+
}
26522641
}
26532642
}

0 commit comments

Comments
 (0)