@@ -193,6 +193,117 @@ Property Let Foo(value)
193
193
Assert . IsFalse ( inspectionResults . Any ( ) ) ;
194
194
}
195
195
196
+ [ TestMethod ]
197
+ [ TestCategory ( "Inspections" ) ]
198
+ public void WriteOnlyProperty_AddPropertyGetQuickFixWorks_ImplicitTypesAndAccessibility ( )
199
+ {
200
+ const string inputCode =
201
+ @"Property Let Foo(value)
202
+ End Property" ;
203
+
204
+ const string expectedCode =
205
+ @"Public Property Get Foo() As Variant
206
+ End Property
207
+ Property Let Foo(value)
208
+ End Property" ;
209
+
210
+ //Arrange
211
+ var builder = new MockVbeBuilder ( ) ;
212
+ var project = builder . ProjectBuilder ( "VBAProject" , vbext_ProjectProtection . vbext_pp_none )
213
+ . AddComponent ( "MyClass" , vbext_ComponentType . vbext_ct_ClassModule , inputCode )
214
+ . Build ( ) ;
215
+ var module = project . Object . VBComponents . Item ( 0 ) . CodeModule ;
216
+ var vbe = builder . AddProject ( project ) . Build ( ) ;
217
+
218
+ var mockHost = new Mock < IHostApplication > ( ) ;
219
+ mockHost . SetupAllProperties ( ) ;
220
+ var parser = MockParser . Create ( vbe . Object , new RubberduckParserState ( new Mock < ISinks > ( ) . Object ) ) ;
221
+
222
+ parser . Parse ( new CancellationTokenSource ( ) ) ;
223
+ if ( parser . State . Status >= ParserState . Error ) { Assert . Inconclusive ( "Parser Error" ) ; }
224
+
225
+ var inspection = new WriteOnlyPropertyInspection ( parser . State ) ;
226
+ var inspectionResults = inspection . GetInspectionResults ( ) ;
227
+
228
+ inspectionResults . First ( ) . QuickFixes . Single ( s => s is WriteOnlyPropertyQuickFix ) . Fix ( ) ;
229
+
230
+ Assert . AreEqual ( expectedCode , module . Lines ( ) ) ;
231
+ }
232
+
233
+ [ TestMethod ]
234
+ [ TestCategory ( "Inspections" ) ]
235
+ public void WriteOnlyProperty_AddPropertyGetQuickFixWorks_ExlicitTypesAndAccessibility ( )
236
+ {
237
+ const string inputCode =
238
+ @"Public Property Let Foo(ByVal value As Integer)
239
+ End Property" ;
240
+
241
+ const string expectedCode =
242
+ @"Public Property Get Foo() As Integer
243
+ End Property
244
+ Public Property Let Foo(ByVal value As Integer)
245
+ End Property" ;
246
+
247
+ //Arrange
248
+ var builder = new MockVbeBuilder ( ) ;
249
+ var project = builder . ProjectBuilder ( "VBAProject" , vbext_ProjectProtection . vbext_pp_none )
250
+ . AddComponent ( "MyClass" , vbext_ComponentType . vbext_ct_ClassModule , inputCode )
251
+ . Build ( ) ;
252
+ var module = project . Object . VBComponents . Item ( 0 ) . CodeModule ;
253
+ var vbe = builder . AddProject ( project ) . Build ( ) ;
254
+
255
+ var mockHost = new Mock < IHostApplication > ( ) ;
256
+ mockHost . SetupAllProperties ( ) ;
257
+ var parser = MockParser . Create ( vbe . Object , new RubberduckParserState ( new Mock < ISinks > ( ) . Object ) ) ;
258
+
259
+ parser . Parse ( new CancellationTokenSource ( ) ) ;
260
+ if ( parser . State . Status >= ParserState . Error ) { Assert . Inconclusive ( "Parser Error" ) ; }
261
+
262
+ var inspection = new WriteOnlyPropertyInspection ( parser . State ) ;
263
+ var inspectionResults = inspection . GetInspectionResults ( ) ;
264
+
265
+ inspectionResults . First ( ) . QuickFixes . Single ( s => s is WriteOnlyPropertyQuickFix ) . Fix ( ) ;
266
+
267
+ Assert . AreEqual ( expectedCode , module . Lines ( ) ) ;
268
+ }
269
+
270
+ [ TestMethod ]
271
+ [ TestCategory ( "Inspections" ) ]
272
+ public void WriteOnlyProperty_AddPropertyGetQuickFixWorks_MultipleParams ( )
273
+ {
274
+ const string inputCode =
275
+ @"Public Property Let Foo(value1, ByVal value2 As Integer, ByRef value3 As Long, value4 As Date, ByVal value5, value6 As String)
276
+ End Property" ;
277
+
278
+ const string expectedCode =
279
+ @"Public Property Get Foo(ByRef value1 As Variant, ByVal value2 As Integer, ByRef value3 As Long, ByRef value4 As Date, ByVal value5 As Variant) As String
280
+ End Property
281
+ Public Property Let Foo(value1, ByVal value2 As Integer, ByRef value3 As Long, value4 As Date, ByVal value5, value6 As String)
282
+ End Property" ;
283
+
284
+ //Arrange
285
+ var builder = new MockVbeBuilder ( ) ;
286
+ var project = builder . ProjectBuilder ( "VBAProject" , vbext_ProjectProtection . vbext_pp_none )
287
+ . AddComponent ( "MyClass" , vbext_ComponentType . vbext_ct_ClassModule , inputCode )
288
+ . Build ( ) ;
289
+ var module = project . Object . VBComponents . Item ( 0 ) . CodeModule ;
290
+ var vbe = builder . AddProject ( project ) . Build ( ) ;
291
+
292
+ var mockHost = new Mock < IHostApplication > ( ) ;
293
+ mockHost . SetupAllProperties ( ) ;
294
+ var parser = MockParser . Create ( vbe . Object , new RubberduckParserState ( new Mock < ISinks > ( ) . Object ) ) ;
295
+
296
+ parser . Parse ( new CancellationTokenSource ( ) ) ;
297
+ if ( parser . State . Status >= ParserState . Error ) { Assert . Inconclusive ( "Parser Error" ) ; }
298
+
299
+ var inspection = new WriteOnlyPropertyInspection ( parser . State ) ;
300
+ var inspectionResults = inspection . GetInspectionResults ( ) ;
301
+
302
+ inspectionResults . First ( ) . QuickFixes . Single ( s => s is WriteOnlyPropertyQuickFix ) . Fix ( ) ;
303
+
304
+ Assert . AreEqual ( expectedCode , module . Lines ( ) ) ;
305
+ }
306
+
196
307
[ TestMethod ]
197
308
[ TestCategory ( "Inspections" ) ]
198
309
public void WriteOnlyProperty_IgnoreQuickFixWorks ( )
0 commit comments