@@ -116,16 +116,16 @@ End Property
116116Public Sub Foo(ByVal arg1 As Integer, ByVal arg2 As String)
117117End Sub
118118
119- Public Function Fizz(ByRef b As Variant) As Variant
119+ Public Function Fizz(b As Variant) As Variant
120120End Function
121121
122122Public Property Get Buzz() As Variant
123123End Property
124124
125- Public Property Let Buzz(ByRef value As Variant)
125+ Public Property Let Buzz(value As Variant)
126126End Property
127127
128- Public Property Set Buzz(ByRef value As Variant)
128+ Public Property Set Buzz(value As Variant)
129129End Property
130130" ;
131131 ExecuteTest ( inputCode , expectedClassCode , expectedInterfaceCode , SelectAllMembers ) ;
@@ -189,7 +189,7 @@ End Function
189189Public Sub Foo(ByVal arg1 As Integer, ByVal arg2 As String)
190190End Sub
191191
192- Public Function Fizz(ByRef b As Variant) As Variant
192+ Public Function Fizz(b As Variant) As Variant
193193End Function
194194" ;
195195 var modelAdjustment = SelectFilteredMembers ( member => ! member . FullMemberSignature . Contains ( "Property" ) ) ;
@@ -414,6 +414,254 @@ End Sub
414414 ExecuteTest ( inputCode , expectedClassCode , expectedInterfaceCode , SelectAllMembers ) ;
415415 }
416416
417+ [ Test ]
418+ [ Category ( "Refactorings" ) ]
419+ [ Category ( "Implement Interface" ) ]
420+ public void ExtractInterfaceRefactoring_ImplicitByRefParameter ( )
421+ {
422+ //Input
423+ const string inputCode =
424+ @"Public Sub Foo(arg As Variant)
425+ End Sub" ;
426+ //Expectation
427+ const string expectedClassCode =
428+ @"Implements IClass
429+
430+ Public Sub Foo(arg As Variant)
431+ End Sub
432+
433+ Private Sub IClass_Foo(arg As Variant)
434+ Err.Raise 5 'TODO implement interface member
435+ End Sub
436+ " ;
437+ const string expectedInterfaceCode =
438+ @"Option Explicit
439+
440+ '@Interface
441+
442+ Public Sub Foo(arg As Variant)
443+ End Sub
444+ " ;
445+ ExecuteTest ( inputCode , expectedClassCode , expectedInterfaceCode , SelectAllMembers ) ;
446+ }
447+
448+ [ Test ]
449+ [ Category ( "Refactorings" ) ]
450+ [ Category ( "Implement Interface" ) ]
451+ public void ExtractInterfaceRefactoring_ExplicitByRefParameter ( )
452+ {
453+ //Input
454+ const string inputCode =
455+ @"Public Sub Foo(ByRef arg As Variant)
456+ End Sub" ;
457+ //Expectation
458+ const string expectedClassCode =
459+ @"Implements IClass
460+
461+ Public Sub Foo(ByRef arg As Variant)
462+ End Sub
463+
464+ Private Sub IClass_Foo(ByRef arg As Variant)
465+ Err.Raise 5 'TODO implement interface member
466+ End Sub
467+ " ;
468+ const string expectedInterfaceCode =
469+ @"Option Explicit
470+
471+ '@Interface
472+
473+ Public Sub Foo(ByRef arg As Variant)
474+ End Sub
475+ " ;
476+ ExecuteTest ( inputCode , expectedClassCode , expectedInterfaceCode , SelectAllMembers ) ;
477+ }
478+
479+ [ Test ]
480+ [ Category ( "Refactorings" ) ]
481+ [ Category ( "Implement Interface" ) ]
482+ public void ExtractInterfaceRefactoring_ByValParameter ( )
483+ {
484+ //Input
485+ const string inputCode =
486+ @"Public Sub Foo(ByVal arg As Variant)
487+ End Sub" ;
488+ //Expectation
489+ const string expectedClassCode =
490+ @"Implements IClass
491+
492+ Public Sub Foo(ByVal arg As Variant)
493+ End Sub
494+
495+ Private Sub IClass_Foo(ByVal arg As Variant)
496+ Err.Raise 5 'TODO implement interface member
497+ End Sub
498+ " ;
499+ const string expectedInterfaceCode =
500+ @"Option Explicit
501+
502+ '@Interface
503+
504+ Public Sub Foo(ByVal arg As Variant)
505+ End Sub
506+ " ;
507+ ExecuteTest ( inputCode , expectedClassCode , expectedInterfaceCode , SelectAllMembers ) ;
508+ }
509+
510+ [ Test ]
511+ [ Category ( "Refactorings" ) ]
512+ [ Category ( "Implement Interface" ) ]
513+ public void ExtractInterfaceRefactoring_OptionalParameter_WoDefault ( )
514+ {
515+ //Input
516+ const string inputCode =
517+ @"Public Sub Foo(Optional arg As Variant)
518+ End Sub" ;
519+ //Expectation
520+ const string expectedClassCode =
521+ @"Implements IClass
522+
523+ Public Sub Foo(Optional arg As Variant)
524+ End Sub
525+
526+ Private Sub IClass_Foo(Optional arg As Variant)
527+ Err.Raise 5 'TODO implement interface member
528+ End Sub
529+ " ;
530+ const string expectedInterfaceCode =
531+ @"Option Explicit
532+
533+ '@Interface
534+
535+ Public Sub Foo(Optional arg As Variant)
536+ End Sub
537+ " ;
538+ ExecuteTest ( inputCode , expectedClassCode , expectedInterfaceCode , SelectAllMembers ) ;
539+ }
540+
541+ [ Test ]
542+ [ Category ( "Refactorings" ) ]
543+ [ Category ( "Implement Interface" ) ]
544+ public void ExtractInterfaceRefactoring_OptionalParameter_WithDefault ( )
545+ {
546+ //Input
547+ const string inputCode =
548+ @"Public Sub Foo(Optional arg As Variant = 42)
549+ End Sub" ;
550+ //Expectation
551+ const string expectedClassCode =
552+ @"Implements IClass
553+
554+ Public Sub Foo(Optional arg As Variant = 42)
555+ End Sub
556+
557+ Private Sub IClass_Foo(Optional arg As Variant = 42)
558+ Err.Raise 5 'TODO implement interface member
559+ End Sub
560+ " ;
561+ const string expectedInterfaceCode =
562+ @"Option Explicit
563+
564+ '@Interface
565+
566+ Public Sub Foo(Optional arg As Variant = 42)
567+ End Sub
568+ " ;
569+ ExecuteTest ( inputCode , expectedClassCode , expectedInterfaceCode , SelectAllMembers ) ;
570+ }
571+
572+ [ Test ]
573+ [ Category ( "Refactorings" ) ]
574+ [ Category ( "Implement Interface" ) ]
575+ public void ExtractInterfaceRefactoring_ParamArray ( )
576+ {
577+ //Input
578+ const string inputCode =
579+ @"Public Sub Foo(arg1 As Long, ParamArray args() As Variant)
580+ End Sub" ;
581+ //Expectation
582+ const string expectedClassCode =
583+ @"Implements IClass
584+
585+ Public Sub Foo(arg1 As Long, ParamArray args() As Variant)
586+ End Sub
587+
588+ Private Sub IClass_Foo(arg1 As Long, ParamArray args() As Variant)
589+ Err.Raise 5 'TODO implement interface member
590+ End Sub
591+ " ;
592+ const string expectedInterfaceCode =
593+ @"Option Explicit
594+
595+ '@Interface
596+
597+ Public Sub Foo(arg1 As Long, ParamArray args() As Variant)
598+ End Sub
599+ " ;
600+ ExecuteTest ( inputCode , expectedClassCode , expectedInterfaceCode , SelectAllMembers ) ;
601+ }
602+
603+ [ Test ]
604+ [ Category ( "Refactorings" ) ]
605+ [ Category ( "Implement Interface" ) ]
606+ public void ExtractInterfaceRefactoring_MakesMissingAsTypesExplicit ( )
607+ {
608+ //Input
609+ const string inputCode =
610+ @"Public Sub Foo(arg1)
611+ End Sub" ;
612+ //Expectation
613+ const string expectedClassCode =
614+ @"Implements IClass
615+
616+ Public Sub Foo(arg1)
617+ End Sub
618+
619+ Private Sub IClass_Foo(arg1 As Variant)
620+ Err.Raise 5 'TODO implement interface member
621+ End Sub
622+ " ;
623+ const string expectedInterfaceCode =
624+ @"Option Explicit
625+
626+ '@Interface
627+
628+ Public Sub Foo(arg1 As Variant)
629+ End Sub
630+ " ;
631+ ExecuteTest ( inputCode , expectedClassCode , expectedInterfaceCode , SelectAllMembers ) ;
632+ }
633+
634+ [ Test ]
635+ [ Category ( "Refactorings" ) ]
636+ [ Category ( "Implement Interface" ) ]
637+ public void ExtractInterfaceRefactoring_Array ( )
638+ {
639+ //Input
640+ const string inputCode =
641+ @"Public Sub Foo(arg1() As Long)
642+ End Sub" ;
643+ //Expectation
644+ const string expectedClassCode =
645+ @"Implements IClass
646+
647+ Public Sub Foo(arg1() As Long)
648+ End Sub
649+
650+ Private Sub IClass_Foo(arg1() As Long)
651+ Err.Raise 5 'TODO implement interface member
652+ End Sub
653+ " ;
654+ const string expectedInterfaceCode =
655+ @"Option Explicit
656+
657+ '@Interface
658+
659+ Public Sub Foo(arg1() As Long)
660+ End Sub
661+ " ;
662+ ExecuteTest ( inputCode , expectedClassCode , expectedInterfaceCode , SelectAllMembers ) ;
663+ }
664+
417665 private void ExecuteTest ( string inputCode , string expectedClassCode , string expectedInterfaceCode , Func < ExtractInterfaceModel , ExtractInterfaceModel > modelAdjustment )
418666 {
419667 var refactoredCode = RefactoredCode (
0 commit comments