@@ -46,16 +46,21 @@ Dim bb As Boolean
4646 Assert . AreEqual ( 1 , inspectionResults . Count ( ) ) ;
4747 }
4848
49+ // this test will eventually be removed once we can fire the inspection on a specific reference
4950 [ TestMethod ]
5051 [ TestCategory ( "Inspections" ) ]
51- public void UnassignedVariableUsage_DoesNotReturnResult ( )
52+ public void UnassignedVariableUsage_ReturnsSingleResult_MultipleReferences ( )
5253 {
5354 const string inputCode =
54- @"Sub Foo()
55- Dim b As Boolean
56- Dim bb As Boolean
57- b = True
58- bb = b
55+ @"Sub tester()
56+ Dim myarr() As Variant
57+ Dim i As Long
58+
59+ ReDim myarr(1 To 10)
60+
61+ For i = LBound(myarr) To UBound(myarr)
62+ Next
63+
5964End Sub" ;
6065
6166 //Arrange
@@ -75,19 +80,18 @@ Dim bb As Boolean
7580 var inspection = new UnassignedVariableUsageInspection ( parser . State ) ;
7681 var inspectionResults = inspection . GetInspectionResults ( ) ;
7782
78- Assert . IsFalse ( inspectionResults . Any ( ) ) ;
83+ Assert . AreEqual ( 1 , inspectionResults . Count ( ) ) ;
7984 }
8085
8186 [ TestMethod ]
8287 [ TestCategory ( "Inspections" ) ]
83- public void UnassignedVariableUsage_Ignored_DoesNotReturnResult ( )
88+ public void UnassignedVariableUsage_DoesNotReturnResult ( )
8489 {
8590 const string inputCode =
8691@"Sub Foo()
8792 Dim b As Boolean
8893 Dim bb As Boolean
89-
90- '@Ignore UnassignedVariableUsage
94+ b = True
9195 bb = b
9296End Sub" ;
9397
@@ -113,28 +117,24 @@ Dim bb As Boolean
113117
114118 [ TestMethod ]
115119 [ TestCategory ( "Inspections" ) ]
116- public void UnassignedVariableUsage_QuickFixWorks ( )
120+ public void UnassignedVariableUsage_Ignored_DoesNotReturnResult ( )
117121 {
118122 const string inputCode =
119123@"Sub Foo()
124+ '@Ignore UnassignedVariableUsage
120125 Dim b As Boolean
121126 Dim bb As Boolean
122- bb = b
123- End Sub" ;
124127
125- const string expectedCode =
126- @"Sub Foo()
127- Dim b As Boolean
128- Dim bb As Boolean
129- TODOTODO = TODO
128+ bb = b
130129End Sub" ;
131130
132131 //Arrange
133132 var builder = new MockVbeBuilder ( ) ;
134- VBComponent component ;
135- var vbe = builder . BuildFromSingleStandardModule ( inputCode , out component ) ;
136- var project = vbe . Object . VBProjects . Item ( 0 ) ;
137- var module = project . VBComponents . Item ( 0 ) . CodeModule ;
133+ var project = builder . ProjectBuilder ( "VBAProject" , vbext_ProjectProtection . vbext_pp_none )
134+ . AddComponent ( "MyClass" , vbext_ComponentType . vbext_ct_ClassModule , inputCode )
135+ . Build ( ) ;
136+ var vbe = builder . AddProject ( project ) . Build ( ) ;
137+
138138 var mockHost = new Mock < IHostApplication > ( ) ;
139139 mockHost . SetupAllProperties ( ) ;
140140 var parser = MockParser . Create ( vbe . Object , new RubberduckParserState ( new Mock < ISinks > ( ) . Object ) ) ;
@@ -145,11 +145,49 @@ Dim bb As Boolean
145145 var inspection = new UnassignedVariableUsageInspection ( parser . State ) ;
146146 var inspectionResults = inspection . GetInspectionResults ( ) ;
147147
148- inspectionResults . First ( ) . QuickFixes . First ( ) . Fix ( ) ;
149-
150- Assert . AreEqual ( expectedCode , module . Lines ( ) ) ;
148+ Assert . IsFalse ( inspectionResults . Any ( ) ) ;
151149 }
152150
151+ // Ignored until we can reinstate the quick fix on a specific reference
152+ // [TestMethod]
153+ // [TestCategory("Inspections")]
154+ // public void UnassignedVariableUsage_QuickFixWorks()
155+ // {
156+ // const string inputCode =
157+ //@"Sub Foo()
158+ // Dim b As Boolean
159+ // Dim bb As Boolean
160+ // bb = b
161+ //End Sub";
162+
163+ // const string expectedCode =
164+ //@"Sub Foo()
165+ // Dim b As Boolean
166+ // Dim bb As Boolean
167+ // TODOTODO = TODO
168+ //End Sub";
169+
170+ // //Arrange
171+ // var builder = new MockVbeBuilder();
172+ // VBComponent component;
173+ // var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
174+ // var project = vbe.Object.VBProjects.Item(0);
175+ // var module = project.VBComponents.Item(0).CodeModule;
176+ // var mockHost = new Mock<IHostApplication>();
177+ // mockHost.SetupAllProperties();
178+ // var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
179+
180+ // parser.Parse(new CancellationTokenSource());
181+ // if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
182+
183+ // var inspection = new UnassignedVariableUsageInspection(parser.State);
184+ // var inspectionResults = inspection.GetInspectionResults();
185+
186+ // inspectionResults.First().QuickFixes.First().Fix();
187+
188+ // Assert.AreEqual(expectedCode, module.Lines());
189+ // }
190+
153191 [ TestMethod ]
154192 [ TestCategory ( "Inspections" ) ]
155193 public void UnassignedVariableUsage_IgnoreQuickFixWorks ( )
@@ -163,9 +201,9 @@ Dim bb As Boolean
163201
164202 const string expectedCode =
165203@"Sub Foo()
204+ '@Ignore UnassignedVariableUsage
166205 Dim b As Boolean
167206 Dim bb As Boolean
168- '@Ignore UnassignedVariableUsage
169207 bb = b
170208End Sub" ;
171209
0 commit comments