Skip to content

Commit c4ad4c8

Browse files
committed
Add ability to extract exposed interfaces to ExtractInterfaceRefactoring
This takes the idea from PR #5357 and adds the implementation in the ExtractInterfaceRefactoringAction according to the current design.
1 parent d5d11de commit c4ad4c8

File tree

6 files changed

+164
-9
lines changed

6 files changed

+164
-9
lines changed

Rubberduck.Parsing/Symbols/ClassModuleDeclaration.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
using Rubberduck.Parsing.Annotations;
22
using Rubberduck.Parsing.ComReflection;
3-
using Rubberduck.Parsing.VBA;
43
using Rubberduck.VBEditor;
54
using System;
65
using System.Collections.Concurrent;

Rubberduck.Refactorings/ExtractInterface/ExtractInterfaceModel.cs

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -6,14 +6,24 @@
66

77
namespace Rubberduck.Refactorings.ExtractInterface
88
{
9+
public enum ClassInstancing
10+
{
11+
Private,
12+
Public
13+
}
14+
915
public class ExtractInterfaceModel : IRefactoringModel
1016
{
1117
public IDeclarationFinderProvider DeclarationFinderProvider { get; }
1218

13-
public Declaration TargetDeclaration { get; }
19+
public ClassModuleDeclaration TargetDeclaration { get; }
1420
public string InterfaceName { get; set; }
1521
public ObservableCollection<InterfaceMember> Members { get; set; } = new ObservableCollection<InterfaceMember>();
1622
public IEnumerable<InterfaceMember> SelectedMembers => Members.Where(m => m.IsSelected);
23+
public ClassInstancing InterfaceInstancing { get; set; }
24+
public ClassInstancing ImplementingClassInstancing => TargetDeclaration.IsExposed
25+
? ClassInstancing.Public
26+
: ClassInstancing.Private;
1727

1828
public static readonly DeclarationType[] MemberTypes =
1929
{
@@ -24,7 +34,7 @@ public class ExtractInterfaceModel : IRefactoringModel
2434
DeclarationType.PropertySet,
2535
};
2636

27-
public ExtractInterfaceModel(IDeclarationFinderProvider declarationFinderProvider, Declaration target)
37+
public ExtractInterfaceModel(IDeclarationFinderProvider declarationFinderProvider, ClassModuleDeclaration target)
2838
{
2939
TargetDeclaration = target;
3040
DeclarationFinderProvider = declarationFinderProvider;
@@ -35,6 +45,7 @@ public ExtractInterfaceModel(IDeclarationFinderProvider declarationFinderProvide
3545
}
3646

3747
InterfaceName = $"I{TargetDeclaration.IdentifierName}";
48+
InterfaceInstancing = ImplementingClassInstancing;
3849

3950
LoadMembers();
4051
}

Rubberduck.Refactorings/ExtractInterface/ExtractInterfaceRefactoring.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -51,12 +51,13 @@ protected override ExtractInterfaceModel InitializeModel(Declaration target)
5151
throw new TargetDeclarationIsNullException();
5252
}
5353

54-
if (!ModuleTypes.Contains(target.DeclarationType))
54+
if (!ModuleTypes.Contains(target.DeclarationType)
55+
|| !(target is ClassModuleDeclaration targetClass))
5556
{
5657
throw new InvalidDeclarationTypeException(target);
5758
}
5859

59-
return new ExtractInterfaceModel(_declarationFinderProvider, target);
60+
return new ExtractInterfaceModel(_declarationFinderProvider, targetClass);
6061
}
6162

6263
protected override void RefactorImpl(ExtractInterfaceModel model)

Rubberduck.Refactorings/ExtractInterface/ExtractInterfaceRefactoringAction.cs

Lines changed: 38 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -63,10 +63,30 @@ private void AddInterface(ExtractInterfaceModel model, IRewriteSession rewriteSe
6363
private void AddInterfaceClass(ExtractInterfaceModel model)
6464
{
6565
var targetProjectId = model.TargetDeclaration.ProjectId;
66-
var interfaceCode = InterfaceModuleBody(model);
66+
var interfaceCode = InterfaceCode(model);
6767
var interfaceName = model.InterfaceName;
6868

69-
_addComponentService.AddComponent(targetProjectId, ComponentType.ClassModule, interfaceCode, componentName: interfaceName);
69+
if (model.InterfaceInstancing == ClassInstancing.Public)
70+
{
71+
_addComponentService.AddComponentWithAttributes(targetProjectId, ComponentType.ClassModule, interfaceCode, componentName: interfaceName);
72+
}
73+
else
74+
{
75+
_addComponentService.AddComponent(targetProjectId, ComponentType.ClassModule, interfaceCode, componentName: interfaceName);
76+
}
77+
}
78+
79+
private static string InterfaceCode(ExtractInterfaceModel model)
80+
{
81+
var interfaceBody = InterfaceModuleBody(model);
82+
83+
if (model.InterfaceInstancing == ClassInstancing.Public)
84+
{
85+
var moduleHeader = ExposedInterfaceHeader(model.InterfaceName);
86+
return $"{moduleHeader}{Environment.NewLine}{interfaceBody}";
87+
}
88+
89+
return interfaceBody;
7090
}
7191

7292
private static string InterfaceModuleBody(ExtractInterfaceModel model)
@@ -80,10 +100,25 @@ private static string InterfaceModuleBody(ExtractInterfaceModel model)
80100
? $"'@{folderAnnotation.Context.GetText()}{Environment.NewLine}"
81101
: string.Empty;
82102

103+
var exposedAnnotation = new ExposedModuleAnnotation();
104+
var exposedAnnotationText = model.InterfaceInstancing == ClassInstancing.Public
105+
? $"'@{exposedAnnotation.Name}{Environment.NewLine}"
106+
: string.Empty;
107+
83108
var interfaceAnnotation = new InterfaceAnnotation();
84109
var interfaceAnnotationText = $"'@{interfaceAnnotation.Name}{Environment.NewLine}";
85110

86-
return $"{optionExplicit}{Environment.NewLine}{folderAnnotationText}{interfaceAnnotationText}{Environment.NewLine}{interfaceMembers}";
111+
return $"{optionExplicit}{Environment.NewLine}{folderAnnotationText}{exposedAnnotationText}{interfaceAnnotationText}{Environment.NewLine}{interfaceMembers}";
112+
}
113+
114+
private static string ExposedInterfaceHeader(string interfaceName)
115+
{
116+
return $@"VERSION 1.0 CLASS
117+
BEGIN
118+
MultiUse = -1 'True
119+
END
120+
Attribute VB_Name = ""{interfaceName}""
121+
Attribute VB_Exposed = True";
87122
}
88123

89124
private void AddImplementsStatement(ExtractInterfaceModel model, IRewriteSession rewriteSession)

RubberduckTests/Refactoring/ExtractInterface/ExtractInterfaceRefactoringActionTests.cs

Lines changed: 52 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -662,6 +662,58 @@ End Sub
662662
ExecuteTest(inputCode, expectedClassCode, expectedInterfaceCode, SelectAllMembers);
663663
}
664664

665+
[Test]
666+
[Category("Refactorings")]
667+
[Category("Implement Interface")]
668+
public void ExtractInterfaceRefactoring_PublicInterfaceInstancingCreatesExposedInterface()
669+
{
670+
671+
//Input
672+
const string inputCode =
673+
@"'@Folder(""MyFolder.MySubFolder"")
674+
675+
Public Sub Foo(ByVal arg1 As Integer, ByVal arg2 As String)
676+
End Sub";
677+
678+
//Expectation
679+
const string expectedClassCode =
680+
@"Implements IClass
681+
682+
'@Folder(""MyFolder.MySubFolder"")
683+
684+
Public Sub Foo(ByVal arg1 As Integer, ByVal arg2 As String)
685+
End Sub
686+
687+
Private Sub IClass_Foo(ByVal arg1 As Integer, ByVal arg2 As String)
688+
Err.Raise 5 'TODO implement interface member
689+
End Sub
690+
";
691+
692+
const string expectedInterfaceCode =
693+
@"VERSION 1.0 CLASS
694+
BEGIN
695+
MultiUse = -1 'True
696+
END
697+
Attribute VB_Name = ""IClass""
698+
Attribute VB_Exposed = True
699+
Option Explicit
700+
701+
'@Folder(""MyFolder.MySubFolder"")
702+
'@Exposed
703+
'@Interface
704+
705+
Public Sub Foo(ByVal arg1 As Integer, ByVal arg2 As String)
706+
End Sub
707+
";
708+
Func<ExtractInterfaceModel, ExtractInterfaceModel> modelAdjustment = model =>
709+
{
710+
var modifiedModel = SelectAllMembers(model);
711+
modifiedModel.InterfaceInstancing = ClassInstancing.Public;
712+
return modifiedModel;
713+
};
714+
ExecuteTest(inputCode, expectedClassCode, expectedInterfaceCode, modelAdjustment);
715+
}
716+
665717
private void ExecuteTest(string inputCode, string expectedClassCode, string expectedInterfaceCode, Func<ExtractInterfaceModel, ExtractInterfaceModel> modelAdjustment)
666718
{
667719
var refactoredCode = RefactoredCode(

RubberduckTests/Refactoring/ExtractInterface/ExtractInterfaceTests.cs

Lines changed: 58 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -144,14 +144,71 @@ public void ExtractInterfaceRefactoring_IgnoresField()
144144
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _, selection);
145145
using(var state = MockParser.CreateAndParse(vbe.Object))
146146
{
147-
var target = state.DeclarationFinder.UserDeclarations(DeclarationType.ClassModule).First();
147+
var target = state.DeclarationFinder
148+
.UserDeclarations(DeclarationType.ClassModule)
149+
.OfType<ClassModuleDeclaration>()
150+
.First();
148151

149152
//Specify Params to remove
150153
var model = new ExtractInterfaceModel(state, target);
151154
Assert.AreEqual(0, model.Members.Count);
152155
}
153156
}
154157

158+
[Test]
159+
[Category("Refactorings")]
160+
[Category("Extract Interface")]
161+
public void ExtractInterfaceRefactoring_DefaultsToPublicInterfaceForExposedImplementingClass()
162+
{
163+
//Input
164+
const string inputCode =
165+
@"Attribute VB_Exposed = True
166+
167+
Public Sub Foo
168+
End Sub";
169+
170+
var selection = new Selection(1, 23, 1, 27);
171+
172+
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _, selection);
173+
using (var state = MockParser.CreateAndParse(vbe.Object))
174+
{
175+
var target = state.DeclarationFinder
176+
.UserDeclarations(DeclarationType.ClassModule)
177+
.OfType<ClassModuleDeclaration>()
178+
.First();
179+
180+
//Specify Params to remove
181+
var model = new ExtractInterfaceModel(state, target);
182+
Assert.AreEqual(ClassInstancing.Public, model.InterfaceInstancing);
183+
}
184+
}
185+
186+
[Test]
187+
[Category("Refactorings")]
188+
[Category("Extract Interface")]
189+
public void ExtractInterfaceRefactoring_DefaultsToPrivateInterfaceForNonExposedImplementingClass()
190+
{
191+
//Input
192+
const string inputCode =
193+
@"Public Sub Foo
194+
End Sub";
195+
196+
var selection = new Selection(1, 23, 1, 27);
197+
198+
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _, selection);
199+
using (var state = MockParser.CreateAndParse(vbe.Object))
200+
{
201+
var target = state.DeclarationFinder
202+
.UserDeclarations(DeclarationType.ClassModule)
203+
.OfType<ClassModuleDeclaration>()
204+
.First();
205+
206+
//Specify Params to remove
207+
var model = new ExtractInterfaceModel(state, target);
208+
Assert.AreEqual(ClassInstancing.Private, model.InterfaceInstancing);
209+
}
210+
}
211+
155212
[Test]
156213
[Category("Refactorings")]
157214
[Category("Extract Interface")]

0 commit comments

Comments
 (0)