@@ -334,6 +334,7 @@ Sub Foo(arg1 As String)
334334 }
335335
336336 [ TestMethod ]
337+ [ TestCategory ( "Inspections" ) ]
337338 public void ParameterCanBeByVal_InterfaceMember_SingleParam ( )
338339 {
339340 //Input
@@ -369,6 +370,43 @@ Private Sub IClass1_DoSomething(ByRef a As Integer)
369370 }
370371
371372 [ TestMethod ]
373+ [ TestCategory ( "Inspections" ) ]
374+ public void ParameterCanBeByVal_InterfaceMember_SingleByValParam ( )
375+ {
376+ //Input
377+ const string inputCode1 =
378+ @"Public Sub DoSomething(ByVal a As Integer)
379+ End Sub" ;
380+ const string inputCode2 =
381+ @"Implements IClass1
382+
383+ Private Sub IClass1_DoSomething(ByVal a As Integer)
384+ End Sub" ;
385+
386+ //Arrange
387+ var builder = new MockVbeBuilder ( ) ;
388+ var project = builder . ProjectBuilder ( "TestProject1" , vbext_ProjectProtection . vbext_pp_none )
389+ . AddComponent ( "IClass1" , vbext_ComponentType . vbext_ct_ClassModule , inputCode1 )
390+ . AddComponent ( "Class1" , vbext_ComponentType . vbext_ct_ClassModule , inputCode2 )
391+ . AddComponent ( "Class2" , vbext_ComponentType . vbext_ct_ClassModule , inputCode2 )
392+ . Build ( ) ;
393+ var vbe = builder . AddProject ( project ) . Build ( ) ;
394+
395+ var mockHost = new Mock < IHostApplication > ( ) ;
396+ mockHost . SetupAllProperties ( ) ;
397+ var parser = MockParser . Create ( vbe . Object , new RubberduckParserState ( vbe . Object , new Mock < ISinks > ( ) . Object ) ) ;
398+
399+ parser . Parse ( new CancellationTokenSource ( ) ) ;
400+ if ( parser . State . Status >= ParserState . Error ) { Assert . Inconclusive ( "Parser Error" ) ; }
401+
402+ var inspection = new ParameterCanBeByValInspection ( parser . State ) ;
403+ var inspectionResults = inspection . GetInspectionResults ( ) ;
404+
405+ Assert . IsFalse ( inspectionResults . Any ( ) ) ;
406+ }
407+
408+ [ TestMethod ]
409+ [ TestCategory ( "Inspections" ) ]
372410 public void ParameterCanBeByVal_InterfaceMember_SingleParamUsedByRef ( )
373411 {
374412 //Input
@@ -405,6 +443,7 @@ Private Sub IClass1_DoSomething(ByRef a As Integer)
405443 }
406444
407445 [ TestMethod ]
446+ [ TestCategory ( "Inspections" ) ]
408447 public void ParameterCanBeByVal_InterfaceMember_MultipleParams_OneCanBeByVal ( )
409448 {
410449 //Input
@@ -446,16 +485,88 @@ Private Sub IClass1_DoSomething(ByRef a As Integer, ByRef b As Integer)
446485 }
447486
448487 [ TestMethod ]
449- public void ParameterCanBeByVal_Event ( )
488+ [ TestCategory ( "Inspections" ) ]
489+ public void ParameterCanBeByVal_EventMember_SingleParam ( )
450490 {
451491 //Input
452492 const string inputCode1 =
453- @"Public Event Foo(ByVal arg1 As Integer, ByVal arg2 As String )" ;
493+ @"Public Event Foo(ByRef arg1 As Integer)" ;
454494
455495 const string inputCode2 =
456496@"Private WithEvents abc As Class1
457497
458- Private Sub abc_Foo(ByVal arg1 As Integer, ByVal arg2 As String)
498+ Private Sub abc_Foo(ByRef arg1 As Integer)
499+ End Sub" ;
500+
501+ //Arrange
502+ var builder = new MockVbeBuilder ( ) ;
503+ var project = builder . ProjectBuilder ( "TestProject1" , vbext_ProjectProtection . vbext_pp_none )
504+ . AddComponent ( "Class1" , vbext_ComponentType . vbext_ct_ClassModule , inputCode1 )
505+ . AddComponent ( "Class2" , vbext_ComponentType . vbext_ct_ClassModule , inputCode2 )
506+ . Build ( ) ;
507+ var vbe = builder . AddProject ( project ) . Build ( ) ;
508+
509+ var mockHost = new Mock < IHostApplication > ( ) ;
510+ mockHost . SetupAllProperties ( ) ;
511+ var parser = MockParser . Create ( vbe . Object , new RubberduckParserState ( vbe . Object , new Mock < ISinks > ( ) . Object ) ) ;
512+
513+ parser . Parse ( new CancellationTokenSource ( ) ) ;
514+ if ( parser . State . Status >= ParserState . Error ) { Assert . Inconclusive ( "Parser Error" ) ; }
515+
516+ var inspection = new ParameterCanBeByValInspection ( parser . State ) ;
517+ var inspectionResults = inspection . GetInspectionResults ( ) ;
518+
519+ Assert . AreEqual ( 1 , inspectionResults . Count ( ) ) ;
520+ }
521+
522+ [ TestMethod ]
523+ [ TestCategory ( "Inspections" ) ]
524+ public void ParameterCanBeByVal_EventMember_SingleByValParam ( )
525+ {
526+ //Input
527+ const string inputCode1 =
528+ @"Public Event Foo(ByVal arg1 As Integer)" ;
529+
530+ const string inputCode2 =
531+ @"Private WithEvents abc As Class1
532+
533+ Private Sub abc_Foo(ByVal arg1 As Integer)
534+ End Sub" ;
535+
536+ //Arrange
537+ var builder = new MockVbeBuilder ( ) ;
538+ var project = builder . ProjectBuilder ( "TestProject1" , vbext_ProjectProtection . vbext_pp_none )
539+ . AddComponent ( "Class1" , vbext_ComponentType . vbext_ct_ClassModule , inputCode1 )
540+ . AddComponent ( "Class2" , vbext_ComponentType . vbext_ct_ClassModule , inputCode2 )
541+ . Build ( ) ;
542+ var vbe = builder . AddProject ( project ) . Build ( ) ;
543+
544+ var mockHost = new Mock < IHostApplication > ( ) ;
545+ mockHost . SetupAllProperties ( ) ;
546+ var parser = MockParser . Create ( vbe . Object , new RubberduckParserState ( vbe . Object , new Mock < ISinks > ( ) . Object ) ) ;
547+
548+ parser . Parse ( new CancellationTokenSource ( ) ) ;
549+ if ( parser . State . Status >= ParserState . Error ) { Assert . Inconclusive ( "Parser Error" ) ; }
550+
551+ var inspection = new ParameterCanBeByValInspection ( parser . State ) ;
552+ var inspectionResults = inspection . GetInspectionResults ( ) ;
553+
554+ Assert . IsFalse ( inspectionResults . Any ( ) ) ;
555+ }
556+
557+ [ TestMethod ]
558+ [ TestCategory ( "Inspections" ) ]
559+ public void ParameterCanBeByVal_EventMember_SingleParamUsedByRef ( )
560+ {
561+ //Input
562+ const string inputCode1 =
563+ @"Public Event Foo(ByRef arg1 As Integer)" ;
564+
565+ const string inputCode2 =
566+ @"Private WithEvents abc As Class1
567+
568+ Private Sub abc_Foo(ByRef arg1 As Integer)
569+ arg1 = 42
459570End Sub" ;
460571
461572 //Arrange
@@ -479,6 +590,42 @@ Private Sub abc_Foo(ByVal arg1 As Integer, ByVal arg2 As String)
479590 Assert . IsFalse ( inspectionResults . Any ( ) ) ;
480591 }
481592
593+ [ TestMethod ]
594+ [ TestCategory ( "Inspections" ) ]
595+ public void ParameterCanBeByVal_EventMember_MultipleParams_OneCanBeByVal ( )
596+ {
597+ //Input
598+ const string inputCode1 =
599+ @"Public Event Foo(ByRef arg1 As Integer, ByRef arg2 As Integer)" ;
600+
601+ const string inputCode2 =
602+ @"Private WithEvents abc As Class1
603+
604+ Private Sub abc_Foo(ByRef arg1 As Integer, ByRef arg2 As Integer)
605+ arg1 = 42
606+ End Sub" ;
607+
608+ //Arrange
609+ var builder = new MockVbeBuilder ( ) ;
610+ var project = builder . ProjectBuilder ( "TestProject1" , vbext_ProjectProtection . vbext_pp_none )
611+ . AddComponent ( "Class1" , vbext_ComponentType . vbext_ct_ClassModule , inputCode1 )
612+ . AddComponent ( "Class2" , vbext_ComponentType . vbext_ct_ClassModule , inputCode2 )
613+ . Build ( ) ;
614+ var vbe = builder . AddProject ( project ) . Build ( ) ;
615+
616+ var mockHost = new Mock < IHostApplication > ( ) ;
617+ mockHost . SetupAllProperties ( ) ;
618+ var parser = MockParser . Create ( vbe . Object , new RubberduckParserState ( vbe . Object , new Mock < ISinks > ( ) . Object ) ) ;
619+
620+ parser . Parse ( new CancellationTokenSource ( ) ) ;
621+ if ( parser . State . Status >= ParserState . Error ) { Assert . Inconclusive ( "Parser Error" ) ; }
622+
623+ var inspection = new ParameterCanBeByValInspection ( parser . State ) ;
624+ var inspectionResults = inspection . GetInspectionResults ( ) ;
625+
626+ Assert . AreEqual ( "arg2" , inspectionResults . Single ( ) . Target . IdentifierName ) ;
627+ }
628+
482629 [ TestMethod ]
483630 [ TestCategory ( "Inspections" ) ]
484631 public void ParameterCanBeByVal_QuickFixWorks_SubNameStartsWithParamName ( )
@@ -639,6 +786,7 @@ public void ParameterCanBeByVal_QuickFixWorks_PassedByRef_MultilineParameter()
639786 }
640787
641788 [ TestMethod ]
789+ [ TestCategory ( "Inspections" ) ]
642790 public void ParameterCanBeByVal_InterfaceMember_MultipleParams_OneCanBeByVal_QuickFixWorks ( )
643791 {
644792 //Input
0 commit comments