Skip to content

Commit d16d94f

Browse files
committed
Fix ImplementInterface regarding optional parameters
1 parent 93939e6 commit d16d94f

File tree

4 files changed

+256
-22
lines changed

4 files changed

+256
-22
lines changed

Rubberduck.Refactorings/ImplementInterface/AddInterfaceImplementations/AddInterfaceImplementationsRefactoringAction.cs

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -85,14 +85,13 @@ private IEnumerable<Parameter> GetParameters(Declaration member)
8585
};
8686
}
8787

88-
return ((ModuleBodyElementDeclaration)member).Parameters.Select(p => new Parameter
88+
if (member is ModuleBodyElementDeclaration method)
8989
{
90-
Accessibility = ((VBAParser.ArgContext)p.Context).BYVAL() != null
91-
? Tokens.ByVal
92-
: Tokens.ByRef,
93-
Name = p.IdentifierName,
94-
AsTypeName = p.AsTypeName
95-
});
90+
return method.Parameters
91+
.Select(parameter => new Parameter(parameter));
92+
}
93+
94+
return Enumerable.Empty<Parameter>();
9695
}
9796
}
9897
}
Lines changed: 45 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,57 @@
1-
namespace Rubberduck.Refactorings.ImplementInterface
1+
using Rubberduck.Parsing.Grammar;
2+
using Rubberduck.Parsing.Symbols;
3+
4+
namespace Rubberduck.Refactorings.ImplementInterface
25
{
36
public class Parameter
47
{
58
public string Accessibility { get; set; }
69
public string Name { get; set; }
710
public string AsTypeName { get; set; }
11+
public string Optional { get; set; }
12+
public string DefaultValue { get; set; }
13+
14+
public Parameter()
15+
{}
16+
17+
public Parameter(ParameterDeclaration parameter)
18+
{
19+
Accessibility = parameter.IsImplicitByRef
20+
? string.Empty
21+
: parameter.IsByRef
22+
? Tokens.ByRef
23+
: Tokens.ByVal;
24+
25+
Name = parameter.IsArray
26+
? $"{parameter.IdentifierName}()"
27+
: parameter.IdentifierName;
28+
29+
AsTypeName = parameter.AsTypeName;
30+
31+
Optional = parameter.IsParamArray
32+
? Tokens.ParamArray
33+
: parameter.IsOptional
34+
? Tokens.Optional
35+
: string.Empty;
36+
37+
DefaultValue = parameter.DefaultValue;
38+
}
39+
40+
private static string FormatStandardElement(string element) => string.IsNullOrEmpty(element)
41+
? string.Empty
42+
: $"{element} ";
43+
44+
private string FormattedAsTypeName => string.IsNullOrEmpty(AsTypeName)
45+
? string.Empty
46+
: $"As {AsTypeName} ";
47+
48+
private string FormattedDefaultValue => string.IsNullOrEmpty(DefaultValue)
49+
? string.Empty
50+
: $"= {DefaultValue}";
851

952
public override string ToString()
1053
{
11-
return $"{Accessibility} {Name} As {AsTypeName}";
54+
return $"{FormatStandardElement(Optional)}{FormatStandardElement(Accessibility)}{FormatStandardElement(Name)}{FormattedAsTypeName}{FormattedDefaultValue}".Trim();
1255
}
1356
}
1457
}

RubberduckTests/Refactoring/ExtractInterface/ExtractInterfaceRefactoringActionTests.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -91,19 +91,19 @@ Private Sub IClass_Foo(ByVal arg1 As Integer, ByVal arg2 As String)
9191
Err.Raise 5 'TODO implement interface member
9292
End Sub
9393
94-
Private Function IClass_Fizz(ByRef b As Variant) As Variant
94+
Private Function IClass_Fizz(b As Variant) As Variant
9595
Err.Raise 5 'TODO implement interface member
9696
End Function
9797
9898
Private Property Get IClass_Buzz() As Variant
9999
Err.Raise 5 'TODO implement interface member
100100
End Property
101101
102-
Private Property Let IClass_Buzz(ByRef value As Variant)
102+
Private Property Let IClass_Buzz(value As Variant)
103103
Err.Raise 5 'TODO implement interface member
104104
End Property
105105
106-
Private Property Set IClass_Buzz(ByRef value As Variant)
106+
Private Property Set IClass_Buzz(value As Variant)
107107
Err.Raise 5 'TODO implement interface member
108108
End Property
109109
";
@@ -176,7 +176,7 @@ Private Sub IClass_Foo(ByVal arg1 As Integer, ByVal arg2 As String)
176176
Err.Raise 5 'TODO implement interface member
177177
End Sub
178178
179-
Private Function IClass_Fizz(ByRef b As Variant) As Variant
179+
Private Function IClass_Fizz(b As Variant) As Variant
180180
Err.Raise 5 'TODO implement interface member
181181
End Function
182182
";

RubberduckTests/Refactoring/ImplementInterface/ImplementInterfaceRefactoringActionTests.cs

Lines changed: 201 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -101,7 +101,7 @@ Private Property Get Interface1_a() As String
101101
Err.Raise 5 'TODO implement interface member
102102
End Property
103103
104-
Private Property Let Interface1_a(ByRef RHS As String)
104+
Private Property Let Interface1_a(RHS As String)
105105
Err.Raise 5 'TODO implement interface member
106106
End Property
107107
@@ -129,7 +129,7 @@ public void ImplementInterface_Procedure_WithParams()
129129
const string expectedCode =
130130
@"Implements Interface1
131131
132-
Private Sub Interface1_Foo(ByVal a As Integer, ByRef b As Variant, ByRef c As Variant, ByRef d As Long)
132+
Private Sub Interface1_Foo(ByVal a As Integer, ByRef b As Variant, c As Variant, d As Long)
133133
Err.Raise 5 'TODO implement interface member
134134
End Sub
135135
";
@@ -201,7 +201,7 @@ public void ImplementInterface_Function_WithParam()
201201
const string expectedCode =
202202
@"Implements Interface1
203203
204-
Private Function Interface1_Foo(ByRef a As Variant) As Variant
204+
Private Function Interface1_Foo(a As Variant) As Variant
205205
Err.Raise 5 'TODO implement interface member
206206
End Function
207207
";
@@ -273,7 +273,7 @@ public void ImplementInterface_PropertyGet_WithParam()
273273
const string expectedCode =
274274
@"Implements Interface1
275275
276-
Private Property Get Interface1_Foo(ByRef a As Variant) As Variant
276+
Private Property Get Interface1_Foo(a As Variant) As Variant
277277
Err.Raise 5 'TODO implement interface member
278278
End Property
279279
";
@@ -321,7 +321,7 @@ public void ImplementInterface_PropertyLet_WithParam()
321321
const string expectedCode =
322322
@"Implements Interface1
323323
324-
Private Property Let Interface1_Foo(ByRef a As Variant)
324+
Private Property Let Interface1_Foo(a As Variant)
325325
Err.Raise 5 'TODO implement interface member
326326
End Property
327327
";
@@ -369,7 +369,7 @@ public void ImplementInterface_PropertySet_WithParam()
369369
const string expectedCode =
370370
@"Implements Interface1
371371
372-
Private Property Set Interface1_Foo(ByRef a As Variant)
372+
Private Property Set Interface1_Foo(a As Variant)
373373
Err.Raise 5 'TODO implement interface member
374374
End Property
375375
";
@@ -454,19 +454,19 @@ Private Sub Interface1_Foo(ByVal arg1 As Integer, ByVal arg2 As String)
454454
Err.Raise 5 'TODO implement interface member
455455
End Sub
456456
457-
Private Function Interface1_Fizz(ByRef b As Variant) As Variant
457+
Private Function Interface1_Fizz(b As Variant) As Variant
458458
Err.Raise 5 'TODO implement interface member
459459
End Function
460460
461461
Private Property Get Interface1_Buzz() As Variant
462462
Err.Raise 5 'TODO implement interface member
463463
End Property
464464
465-
Private Property Let Interface1_Buzz(ByRef value As Variant)
465+
Private Property Let Interface1_Buzz(value As Variant)
466466
Err.Raise 5 'TODO implement interface member
467467
End Property
468468
469-
Private Property Set Interface1_Buzz(ByRef value As Variant)
469+
Private Property Set Interface1_Buzz(value As Variant)
470470
Err.Raise 5 'TODO implement interface member
471471
End Property
472472
";
@@ -554,6 +554,198 @@ End Property
554554
ExecuteTest(classCode, interfaceCode, expectedCode);
555555
}
556556

557+
[Test]
558+
[Category("Refactorings")]
559+
[Category("Implement Interface")]
560+
public void ImplementInterface_ImplicitByRefParameter()
561+
{
562+
//Input
563+
const string interfaceCode =
564+
@"Public Sub Foo(arg As Variant)
565+
End Sub";
566+
567+
const string classCode =
568+
@"Implements Interface1";
569+
570+
//Expectation
571+
const string expectedCode =
572+
@"Implements Interface1
573+
574+
Private Sub Interface1_Foo(arg As Variant)
575+
Err.Raise 5 'TODO implement interface member
576+
End Sub
577+
";
578+
ExecuteTest(classCode, interfaceCode, expectedCode);
579+
}
580+
581+
[Test]
582+
[Category("Refactorings")]
583+
[Category("Implement Interface")]
584+
public void ImplementInterface_ExplicitByRefParameter()
585+
{
586+
//Input
587+
const string interfaceCode =
588+
@"Public Sub Foo(ByRef arg As Variant)
589+
End Sub";
590+
591+
const string classCode =
592+
@"Implements Interface1";
593+
594+
//Expectation
595+
const string expectedCode =
596+
@"Implements Interface1
597+
598+
Private Sub Interface1_Foo(ByRef arg As Variant)
599+
Err.Raise 5 'TODO implement interface member
600+
End Sub
601+
";
602+
ExecuteTest(classCode, interfaceCode, expectedCode);
603+
}
604+
605+
[Test]
606+
[Category("Refactorings")]
607+
[Category("Implement Interface")]
608+
public void ImplementInterface_ByValParameter()
609+
{
610+
//Input
611+
const string interfaceCode =
612+
@"Public Sub Foo(ByVal arg As Variant)
613+
End Sub";
614+
615+
const string classCode =
616+
@"Implements Interface1";
617+
618+
//Expectation
619+
const string expectedCode =
620+
@"Implements Interface1
621+
622+
Private Sub Interface1_Foo(ByVal arg As Variant)
623+
Err.Raise 5 'TODO implement interface member
624+
End Sub
625+
";
626+
ExecuteTest(classCode, interfaceCode, expectedCode);
627+
}
628+
629+
[Test]
630+
[Category("Refactorings")]
631+
[Category("Implement Interface")]
632+
public void ImplementInterface_OptionalParameter_WoDefault()
633+
{
634+
//Input
635+
const string interfaceCode =
636+
@"Public Sub Foo(Optional arg As Variant)
637+
End Sub";
638+
639+
const string classCode =
640+
@"Implements Interface1";
641+
642+
//Expectation
643+
const string expectedCode =
644+
@"Implements Interface1
645+
646+
Private Sub Interface1_Foo(Optional arg As Variant)
647+
Err.Raise 5 'TODO implement interface member
648+
End Sub
649+
";
650+
ExecuteTest(classCode, interfaceCode, expectedCode);
651+
}
652+
653+
[Test]
654+
[Category("Refactorings")]
655+
[Category("Implement Interface")]
656+
public void ImplementInterface_OptionalParameter_WithDefault()
657+
{
658+
//Input
659+
const string interfaceCode =
660+
@"Public Sub Foo(Optional arg As Variant = 42)
661+
End Sub";
662+
663+
const string classCode =
664+
@"Implements Interface1";
665+
666+
//Expectation
667+
const string expectedCode =
668+
@"Implements Interface1
669+
670+
Private Sub Interface1_Foo(Optional arg As Variant = 42)
671+
Err.Raise 5 'TODO implement interface member
672+
End Sub
673+
";
674+
ExecuteTest(classCode, interfaceCode, expectedCode);
675+
}
676+
677+
[Test]
678+
[Category("Refactorings")]
679+
[Category("Implement Interface")]
680+
public void ImplementInterface_ParamArray()
681+
{
682+
//Input
683+
const string interfaceCode =
684+
@"Public Sub Foo(arg1 As Long, ParamArray args() As Variant)
685+
End Sub";
686+
687+
const string classCode =
688+
@"Implements Interface1";
689+
690+
//Expectation
691+
const string expectedCode =
692+
@"Implements Interface1
693+
694+
Private Sub Interface1_Foo(arg1 As Long, ParamArray args() As Variant)
695+
Err.Raise 5 'TODO implement interface member
696+
End Sub
697+
";
698+
ExecuteTest(classCode, interfaceCode, expectedCode);
699+
}
700+
701+
[Test]
702+
[Category("Refactorings")]
703+
[Category("Implement Interface")]
704+
public void ImplementInterface_MakesMissingAsTypesExplicit()
705+
{
706+
//Input
707+
const string interfaceCode =
708+
@"Public Sub Foo(arg1)
709+
End Sub";
710+
711+
const string classCode =
712+
@"Implements Interface1";
713+
714+
//Expectation
715+
const string expectedCode =
716+
@"Implements Interface1
717+
718+
Private Sub Interface1_Foo(arg1 As Variant)
719+
Err.Raise 5 'TODO implement interface member
720+
End Sub
721+
";
722+
ExecuteTest(classCode, interfaceCode, expectedCode);
723+
}
724+
725+
[Test]
726+
[Category("Refactorings")]
727+
[Category("Implement Interface")]
728+
public void ImplementInterface_Array()
729+
{
730+
//Input
731+
const string interfaceCode =
732+
@"Public Sub Foo(arg1() As Long)
733+
End Sub";
734+
735+
const string classCode =
736+
@"Implements Interface1";
737+
738+
//Expectation
739+
const string expectedCode =
740+
@"Implements Interface1
741+
742+
Private Sub Interface1_Foo(arg1() As Long)
743+
Err.Raise 5 'TODO implement interface member
744+
End Sub
745+
";
746+
ExecuteTest(classCode, interfaceCode, expectedCode);
747+
}
748+
557749
private void ExecuteTest(string classCode, string interfaceCode, string expectedClassCode)
558750
{
559751
var refactoredCode = RefactoredCode(

0 commit comments

Comments
 (0)