Skip to content

Commit 01aaa1a

Browse files
committed
Use InspectionResultsForModules libraries overload
1 parent ec9dbb5 commit 01aaa1a

File tree

1 file changed

+25
-62
lines changed

1 file changed

+25
-62
lines changed

RubberduckTests/Inspections/ObjectVariableNotSetInspectionTests.cs

Lines changed: 25 additions & 62 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,10 @@
1-
using System;
21
using System.Linq;
3-
using System.Threading;
42
using NUnit.Framework;
53
using Rubberduck.Inspections.Concrete;
64
using Rubberduck.Parsing.Inspections.Abstract;
7-
using Rubberduck.Parsing.Symbols;
85
using Rubberduck.Parsing.VBA;
96
using Rubberduck.VBEditor;
107
using Rubberduck.VBEditor.SafeComWrappers;
11-
using RubberduckTests.Mocks;
128

139
namespace RubberduckTests.Inspections
1410
{
@@ -144,7 +140,7 @@ Dim target As String
144140
target = Range(""A1"")
145141
target.Value = ""all good""
146142
End Sub";
147-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel.1.8.xml");
143+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel");
148144
}
149145

150146
[Test]
@@ -160,7 +156,7 @@ Dim target As Collection
160156
testParam = target
161157
testParam.Add 100
162158
End Sub";
163-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "VBA.4.2.xml");
159+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "VBA");
164160
}
165161

166162
[Test]
@@ -196,7 +192,7 @@ public void ObjectVariableNotSet_GivenVariantVariableAssignedNewObject_ReturnsRe
196192
Private Sub TestSub(ByRef testParam As Variant)
197193
testParam = New Collection
198194
End Sub";
199-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "VBA.4.2.xml");
195+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "VBA");
200196
}
201197

202198
[Test]
@@ -229,7 +225,7 @@ Dim target As Range
229225
target.Value = ""forgot something?""
230226
231227
End Sub";
232-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel.1.8.xml");
228+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel");
233229
}
234230

235231
[Test]
@@ -247,7 +243,7 @@ Dim target As Range
247243
target.Value = ""All good""
248244
249245
End Sub";
250-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel.1.8.xml");
246+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel");
251247
}
252248

253249
[Test]
@@ -289,7 +285,7 @@ Private Sub TestSelfAssigned()
289285
Dim arg1 As new Collection
290286
arg1.Add 7
291287
End Sub";
292-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "VBA.4.2.xml");
288+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "VBA");
293289
}
294290

295291
[Test]
@@ -346,7 +342,7 @@ public void ObjectVariableNotSet_FunctionReturnNotSet_ReturnsResult()
346342
Private Function Test() As Collection
347343
Test = New Collection
348344
End Function";
349-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "VBA.4.2.xml");
345+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "VBA");
350346
}
351347

352348
[Test]
@@ -497,7 +493,7 @@ Dim bar As Collection
497493
bar.Add ""x"", ""x""
498494
foo = ""Test"" & bar.Item(""x"")
499495
End Sub";
500-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "VBA.4.2");
496+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "VBA");
501497
}
502498

503499
[Test]
@@ -531,7 +527,7 @@ Dim foo As Range
531527
Dim bar As Variant
532528
bar = foo
533529
End Sub";
534-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel.1.8.xml");
530+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "Excel");
535531
}
536532

537533
[Test]
@@ -547,7 +543,7 @@ Dim bar As Variant
547543
bar = foo
548544
End Sub";
549545
//The default member of Recordset is Fields, which is an object.
550-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "ADODB.6.1");
546+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "ADODB");
551547
}
552548

553549
[Test]
@@ -563,7 +559,7 @@ Dim bar As Variant
563559
foo = bar
564560
End Sub";
565561
//The default member of Recordset is Fields, which is an object and only has a paramterized default member.
566-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "ADODB.6.1");
562+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "ADODB");
567563
}
568564

569565
[Test]
@@ -577,7 +573,7 @@ Private Sub Test()
577573
Dim foo As Variant
578574
foo = New Connection
579575
End Sub";
580-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "ADODB.6.1");
576+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "ADODB");
581577
}
582578

583579
[Test]
@@ -592,7 +588,7 @@ Dim foo As Variant
592588
foo = New Recordset
593589
End Sub";
594590
//The default member of Recordset is Fields, which is an object.
595-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "ADODB.6.1");
591+
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount, "ADODB");
596592
}
597593

598594
[Test]
@@ -762,12 +758,11 @@ Private Sub Baz(arg As Variant)
762758
End Sub
763759
";
764760

765-
var vbe = MockVbeBuilder.BuildFromModules(
761+
var inspectionResults = InspectionResultsForModules(
766762
("Class1", class1Code, ComponentType.ClassModule),
767763
("Class2", class2Code, ComponentType.ClassModule),
768764
("Module1", moduleCode, ComponentType.StandardModule));
769765

770-
var inspectionResults = InspectionResults(vbe.Object);
771766
Assert.IsFalse(inspectionResults.Any());
772767
}
773768

@@ -850,12 +845,11 @@ Private Sub Baz(arg As Variant)
850845
End Sub
851846
";
852847

853-
var vbe = MockVbeBuilder.BuildFromModules(
848+
var inspectionResults = InspectionResultsForModules(
854849
("Class1", class1Code, ComponentType.ClassModule),
855850
("Class2", class2Code, ComponentType.ClassModule),
856851
("Module1", moduleCode, ComponentType.StandardModule));
857852

858-
var inspectionResults = InspectionResults(vbe.Object);
859853
Assert.IsFalse(inspectionResults.Any());
860854
}
861855

@@ -942,13 +936,12 @@ Private Sub Baz(arg As Variant)
942936
End Sub
943937
";
944938

945-
var vbe = MockVbeBuilder.BuildFromModules(
939+
var inspectionResults = InspectionResultsForModules(
946940
("Class1", class1Code, ComponentType.ClassModule),
947941
("Class2", class2Code, ComponentType.ClassModule),
948942
("Class3", class3Code, ComponentType.ClassModule),
949943
("Module1", moduleCode, ComponentType.StandardModule));
950944

951-
var inspectionResults = InspectionResults(vbe.Object);
952945
Assert.IsFalse(inspectionResults.Any());
953946
}
954947

@@ -1035,13 +1028,12 @@ Private Sub Baz(arg As Variant)
10351028
End Sub
10361029
";
10371030

1038-
var vbe = MockVbeBuilder.BuildFromModules(
1031+
var inspectionResults = InspectionResultsForModules(
10391032
("Class1", class1Code, ComponentType.ClassModule),
10401033
("Class2", class2Code, ComponentType.ClassModule),
10411034
("Class3", class3Code, ComponentType.ClassModule),
10421035
("Module1", moduleCode, ComponentType.StandardModule));
10431036

1044-
var inspectionResults = InspectionResults(vbe.Object);
10451037
Assert.IsFalse(inspectionResults.Any());
10461038
}
10471039

@@ -1128,13 +1120,12 @@ Private Sub Baz(arg As Variant)
11281120
End Sub
11291121
";
11301122

1131-
var vbe = MockVbeBuilder.BuildFromModules(
1123+
var inspectionResults = InspectionResultsForModules(
11321124
("Class1", class1Code, ComponentType.ClassModule),
11331125
("Class2", class2Code, ComponentType.ClassModule),
11341126
("Class3", class3Code, ComponentType.ClassModule),
11351127
("Module1", moduleCode, ComponentType.StandardModule));
11361128

1137-
var inspectionResults = InspectionResults(vbe.Object);
11381129
Assert.IsFalse(inspectionResults.Any());
11391130
}
11401131

@@ -1186,13 +1177,12 @@ Private Sub Baz(arg As Variant)
11861177
End Sub
11871178
";
11881179

1189-
var vbe = MockVbeBuilder.BuildFromModules(
1180+
var inspectionResults = InspectionResultsForModules(
11901181
("Class1", class1Code, ComponentType.ClassModule),
11911182
("Class2", class2Code, ComponentType.ClassModule),
11921183
("Class3", class3Code, ComponentType.ClassModule),
11931184
("Module1", moduleCode, ComponentType.StandardModule));
11941185

1195-
var inspectionResults = InspectionResults(vbe.Object);
11961186
var inspectionResult = inspectionResults.Single();
11971187

11981188
var expectedSelection = new Selection(6, selectionStartColumn, 6, selectionEndColumn);
@@ -1249,13 +1239,12 @@ Private Sub Baz(arg As Variant)
12491239
End Sub
12501240
";
12511241

1252-
var vbe = MockVbeBuilder.BuildFromModules(
1242+
var inspectionResults = InspectionResultsForModules(
12531243
("Class1", class1Code, ComponentType.ClassModule),
12541244
("Class2", class2Code, ComponentType.ClassModule),
12551245
("Class3", class3Code, ComponentType.ClassModule),
12561246
("Module1", moduleCode, ComponentType.StandardModule));
12571247

1258-
var inspectionResults = InspectionResults(vbe.Object);
12591248
var inspectionResult = inspectionResults.Single();
12601249

12611250
var expectedSelection = new Selection(6, selectionStartColumn, 6, selectionEndColumn);
@@ -1312,13 +1301,12 @@ Private Sub Baz(arg As Variant)
13121301
End Sub
13131302
";
13141303

1315-
var vbe = MockVbeBuilder.BuildFromModules(
1304+
var inspectionResults = InspectionResultsForModules(
13161305
("Class1", class1Code, ComponentType.ClassModule),
13171306
("Class2", class2Code, ComponentType.ClassModule),
13181307
("Class3", class3Code, ComponentType.ClassModule),
13191308
("Module1", moduleCode, ComponentType.StandardModule));
13201309

1321-
var inspectionResults = InspectionResults(vbe.Object);
13221310
var inspectionResult = inspectionResults.Single();
13231311

13241312
var expectedSelection = new Selection(6, selectionStartColumn, 6, selectionEndColumn);
@@ -1364,12 +1352,11 @@ Private Sub Baz(arg As Variant)
13641352
End Sub
13651353
";
13661354

1367-
var vbe = MockVbeBuilder.BuildFromModules(
1355+
var inspectionResults = InspectionResultsForModules(
13681356
("Class1", class1Code, ComponentType.ClassModule),
13691357
("Class2", class2Code, ComponentType.ClassModule),
13701358
("Module1", moduleCode, ComponentType.StandardModule));
13711359

1372-
var inspectionResults = InspectionResults(vbe.Object);
13731360
var inspectionResult = inspectionResults.Single();
13741361

13751362
var expectedSelection = new Selection(4, selectionStartColumn, 4, selectionEndColumn);
@@ -1410,13 +1397,11 @@ Dim fooBar As New Class1
14101397
End Function
14111398
";
14121399

1413-
var vbe = MockVbeBuilder.BuildFromModules(
1400+
var inspectionResults = InspectionResultsForModules(
14141401
("Class1", class1Code, ComponentType.ClassModule),
14151402
("Class2", class2Code, ComponentType.ClassModule),
14161403
("Module1", moduleCode, ComponentType.StandardModule));
14171404

1418-
var inspectionResults = InspectionResults(vbe.Object);
1419-
14201405
Assert.IsFalse(inspectionResults.Any());
14211406
}
14221407

@@ -1427,30 +1412,8 @@ protected override IInspection InspectionUnderTest(RubberduckParserState state)
14271412

14281413
private void AssertInputCodeYieldsExpectedInspectionResultCount(string inputCode, int expected, params string[] testLibraries)
14291414
{
1430-
var builder = new MockVbeBuilder();
1431-
var projectBuilder = builder.ProjectBuilder("TestProject1", "TestProject1", ProjectProtection.Unprotected)
1432-
.AddComponent("Class1", ComponentType.ClassModule, inputCode);
1433-
1434-
foreach (var testLibrary in testLibraries)
1435-
{
1436-
var libraryDescriptionComponents = testLibrary.Split('.');
1437-
var libraryName = libraryDescriptionComponents[0];
1438-
var libraryPath = MockVbeBuilder.LibraryPaths[libraryName];
1439-
int majorVersion = Int32.Parse(libraryDescriptionComponents[1]);
1440-
int minorVersion = Int32.Parse(libraryDescriptionComponents[2]);
1441-
projectBuilder.AddReference(libraryName, libraryPath, majorVersion, minorVersion, true);
1442-
}
1443-
1444-
var project = projectBuilder.Build();
1445-
var vbe = builder.AddProject(project).Build();
1446-
1447-
using (var state = MockParser.CreateAndParse(vbe.Object))
1448-
{
1449-
var inspection = InspectionUnderTest(state);
1450-
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
1451-
1452-
Assert.AreEqual(expected, inspectionResults.Count());
1453-
}
1415+
var inspectionResults = InspectionResultsForModules(("Class1", inputCode, ComponentType.ClassModule), testLibraries);
1416+
Assert.AreEqual(expected, inspectionResults.Count());
14541417
}
14551418
}
14561419
}

0 commit comments

Comments
 (0)