Skip to content

Commit 50299d8

Browse files
committed
Add tests for MoveToFolderRefactoring itself
Also adds members to get the initial model to InteractiveRefactoringTestsBase.
1 parent 7b2b173 commit 50299d8

File tree

5 files changed

+322
-0
lines changed

5 files changed

+322
-0
lines changed

Rubberduck.Refactorings/MoveFolder/MoveContainingFolderRefactoring.cs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,11 @@ protected override Declaration FindTargetDeclaration(QualifiedSelection targetSe
4141

4242
protected override MoveMultipleFoldersModel InitializeModel(Declaration target)
4343
{
44+
if (target == null)
45+
{
46+
throw new TargetDeclarationIsNullException();
47+
}
48+
4449
if (!(target is ModuleDeclaration targetModule))
4550
{
4651
throw new InvalidDeclarationTypeException(target);

Rubberduck.Refactorings/MoveToFolder/MoveToFolderRefactoring.cs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,11 @@ protected override Declaration FindTargetDeclaration(QualifiedSelection targetSe
3737

3838
protected override MoveMultipleToFolderModel InitializeModel(Declaration target)
3939
{
40+
if (target == null)
41+
{
42+
throw new TargetDeclarationIsNullException();
43+
}
44+
4045
if (!(target is ModuleDeclaration targetModule))
4146
{
4247
throw new InvalidDeclarationTypeException(target);

RubberduckTests/Refactoring/InteractiveRefactoringTestBase.cs

Lines changed: 94 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
using Rubberduck.Parsing.Symbols;
88
using Rubberduck.Parsing.VBA;
99
using Rubberduck.Refactorings;
10+
using Rubberduck.Refactorings.Exceptions;
1011
using Rubberduck.VBEditor;
1112
using Rubberduck.VBEditor.SafeComWrappers;
1213
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
@@ -116,6 +117,99 @@ protected IDictionary<string, string> RefactoredCode(IVBE vbe, string declaratio
116117
}
117118
}
118119

120+
protected TModel InitialModel(string code, Selection selection, bool executeViaActiveSelection = false)
121+
{
122+
var vbe = TestVbe(code, out _);
123+
var componentName = vbe.SelectedVBComponent.Name;
124+
return InitialModel(vbe, componentName, selection, executeViaActiveSelection);
125+
}
126+
127+
protected TModel InitialModel(string selectedComponentName, Selection selection, bool executeViaActiveSelection = false, params (string componentName, string content, ComponentType componentType)[] modules)
128+
{
129+
var vbe = TestVbe(modules);
130+
return InitialModel(vbe, selectedComponentName, selection, executeViaActiveSelection);
131+
}
132+
133+
protected TModel InitialModel(IVBE vbe, string selectedComponentName, Selection selection, bool executeViaActiveSelection = false)
134+
{
135+
var (state, rewritingManager) = MockParser.CreateAndParseWithRewritingManager(vbe);
136+
using (state)
137+
{
138+
TModel initialModel = null;
139+
Func<TModel, TModel> exfiltrationAction = model =>
140+
{
141+
initialModel = model;
142+
throw new RefactoringAbortedException();
143+
};
144+
145+
var module = state.DeclarationFinder.UserDeclarations(DeclarationType.Module)
146+
.Single(declaration => declaration.IdentifierName == selectedComponentName)
147+
.QualifiedModuleName;
148+
var qualifiedSelection = new QualifiedSelection(module, selection);
149+
150+
var refactoring = executeViaActiveSelection
151+
? TestRefactoring(rewritingManager, state, exfiltrationAction, qualifiedSelection)
152+
: TestRefactoring(rewritingManager, state, exfiltrationAction);
153+
154+
try
155+
{
156+
if (executeViaActiveSelection)
157+
{
158+
refactoring.Refactor();
159+
}
160+
else
161+
{
162+
refactoring.Refactor(qualifiedSelection);
163+
}
164+
}
165+
catch (RefactoringAbortedException)
166+
{}
167+
168+
return initialModel;
169+
}
170+
}
171+
172+
protected TModel InitialModel(string code, string declarationName, DeclarationType declarationType)
173+
{
174+
var vbe = TestVbe(code, out _);
175+
var componentName = vbe.SelectedVBComponent.Name;
176+
return InitialModel(vbe, declarationName, declarationType);
177+
}
178+
179+
protected TModel InitialModel(string declarationName, DeclarationType declarationType, params (string componentName, string content, ComponentType componentType)[] modules)
180+
{
181+
var vbe = TestVbe(modules);
182+
return InitialModel(vbe, declarationName, declarationType);
183+
}
184+
185+
protected TModel InitialModel(IVBE vbe, string declarationName, DeclarationType declarationType)
186+
{
187+
var (state, rewritingManager) = MockParser.CreateAndParseWithRewritingManager(vbe);
188+
using (state)
189+
{
190+
var target = state.DeclarationFinder.DeclarationsWithType(declarationType)
191+
.Single(declaration => declaration.IdentifierName == declarationName);
192+
193+
TModel initialModel = null;
194+
Func<TModel,TModel> exfiltrationAction = model =>
195+
{
196+
initialModel = model;
197+
throw new RefactoringAbortedException();
198+
};
199+
200+
var refactoring = TestRefactoring(rewritingManager, state, exfiltrationAction);
201+
202+
try
203+
{
204+
refactoring.Refactor(target);
205+
}
206+
catch (RefactoringAbortedException)
207+
{}
208+
209+
return initialModel;
210+
}
211+
}
212+
119213
protected override IRefactoring TestRefactoring(
120214
IRewritingManager rewritingManager,
121215
RubberduckParserState state,
Lines changed: 218 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,218 @@
1+
using System;
2+
using System.Linq;
3+
using Moq;
4+
using NUnit.Framework;
5+
using Rubberduck.Parsing.Rewriter;
6+
using Rubberduck.Parsing.Symbols;
7+
using Rubberduck.Parsing.UIContext;
8+
using Rubberduck.Parsing.VBA;
9+
using Rubberduck.Refactorings;
10+
using Rubberduck.Refactorings.Exceptions;
11+
using Rubberduck.Refactorings.MoveToFolder;
12+
using Rubberduck.VBEditor.SafeComWrappers;
13+
using Rubberduck.VBEditor.Utility;
14+
using RubberduckTests.Mocks;
15+
16+
namespace RubberduckTests.Refactoring.MoveToFolder
17+
{
18+
[TestFixture]
19+
public class MoveToFolderRefactoringTests : InteractiveRefactoringTestBase<IMoveMultipleToFolderPresenter, MoveMultipleToFolderModel>
20+
{
21+
[Test]
22+
[Category("Refactorings")]
23+
public void MoveToFolderRefactoring_NoAnnotation()
24+
{
25+
const string code = @"
26+
Public Sub Foo()
27+
End Sub
28+
";
29+
const string expectedCode = @"'@Folder ""MyNewFolder.MySubFolder""
30+
31+
Public Sub Foo()
32+
End Sub
33+
";
34+
Func<MoveMultipleToFolderModel, MoveMultipleToFolderModel> presenterAction = (model) =>
35+
{
36+
model.TargetFolder = "MyNewFolder.MySubFolder";
37+
return model;
38+
};
39+
40+
var refactoredCode = RefactoredCode(
41+
"TestModule",
42+
DeclarationType.Module,
43+
presenterAction,
44+
null,
45+
("TestModule", code, ComponentType.StandardModule));
46+
47+
Assert.AreEqual(expectedCode, refactoredCode["TestModule"]);
48+
}
49+
50+
[Test]
51+
[Category("Refactorings")]
52+
public void MoveToFolderRefactoring_UpdateAnnotation()
53+
{
54+
const string code = @"
55+
'@Folder(""MyOldFolder.MyOldSubfolder.SubSub"")
56+
Public Sub Foo()
57+
End Sub
58+
";
59+
const string expectedCode = @"
60+
'@Folder ""MyNewFolder.MySubFolder""
61+
Public Sub Foo()
62+
End Sub
63+
";
64+
Func<MoveMultipleToFolderModel, MoveMultipleToFolderModel> presenterAction = (model) =>
65+
{
66+
model.TargetFolder = "MyNewFolder.MySubFolder";
67+
return model;
68+
};
69+
70+
var refactoredCode = RefactoredCode(
71+
"TestModule",
72+
DeclarationType.Module,
73+
presenterAction,
74+
null,
75+
("TestModule", code, ComponentType.StandardModule));
76+
77+
Assert.AreEqual(expectedCode, refactoredCode["TestModule"]);
78+
}
79+
80+
[Test]
81+
[Category("Refactorings")]
82+
public void MoveToFolderRefactoring_NameContainingDoubleQuotes()
83+
{
84+
const string code = @"
85+
Public Sub Foo()
86+
End Sub
87+
";
88+
const string expectedCode = @"'@Folder ""MyNew""""Folder.My""""""""""""""""SubFolder""
89+
90+
Public Sub Foo()
91+
End Sub
92+
";
93+
Func<MoveMultipleToFolderModel, MoveMultipleToFolderModel> presenterAction = (model) =>
94+
{
95+
model.TargetFolder = "MyNew\"Folder.My\"\"\"\"SubFolder";
96+
return model;
97+
};
98+
99+
var refactoredCode = RefactoredCode(
100+
"TestModule",
101+
DeclarationType.Module,
102+
presenterAction,
103+
null,
104+
("TestModule", code, ComponentType.StandardModule));
105+
106+
Assert.AreEqual(expectedCode, refactoredCode["TestModule"]);
107+
}
108+
109+
110+
[Test]
111+
[Category("Refactorings")]
112+
public void MoveToFolderRefactoring_InitialModel_NoAnnotation()
113+
{
114+
const string code = @"
115+
Public Sub Foo()
116+
End Sub
117+
";
118+
var vbe = new MockVbeBuilder()
119+
.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
120+
.AddComponent("TestModule", ComponentType.StandardModule, code)
121+
.AddProjectToVbeBuilder()
122+
.Build()
123+
.Object;
124+
125+
var model = InitialModel(vbe, "TestModule", DeclarationType.ProceduralModule);
126+
127+
var targetName = model.Targets.Single().IdentifierName;
128+
var initialTargetFolder = model.TargetFolder;
129+
130+
Assert.AreEqual("TestModule", targetName);
131+
Assert.AreEqual("TestProject", initialTargetFolder);
132+
}
133+
134+
[Test]
135+
[Category("Refactorings")]
136+
public void MoveToFolderRefactoring_InitialModel_UpdateAnnotation()
137+
{
138+
const string code = @"
139+
'@Folder(""MyOldFolder.MyOldSubfolder.SubSub"")
140+
Public Sub Foo()
141+
End Sub
142+
";
143+
var model = InitialModel(
144+
"TestModule",
145+
DeclarationType.ProceduralModule,
146+
("TestModule", code, ComponentType.StandardModule));
147+
148+
var targetName = model.Targets.Single().IdentifierName;
149+
var initialTargetFolder = model.TargetFolder;
150+
151+
Assert.AreEqual("TestModule", targetName);
152+
Assert.AreEqual("MyOldFolder.MyOldSubfolder.SubSub", initialTargetFolder);
153+
}
154+
155+
[Test]
156+
[Category("Refactorings")]
157+
public void MoveToFolderRefactoring_InitialModel_NameContainingDoubleQuotes()
158+
{
159+
const string code = @"
160+
'@Folder(""MyNew""""Folder.My""""""""""""""""SubFolder"")
161+
Public Sub Foo()
162+
End Sub
163+
";
164+
var model = InitialModel(
165+
"TestModule",
166+
DeclarationType.ProceduralModule,
167+
("TestModule", code, ComponentType.StandardModule));
168+
169+
var targetName = model.Targets.Single().IdentifierName;
170+
var initialTargetFolder = model.TargetFolder;
171+
172+
Assert.AreEqual("TestModule", targetName);
173+
Assert.AreEqual("MyNew\"Folder.My\"\"\"\"SubFolder", initialTargetFolder);
174+
}
175+
176+
[Test]
177+
[Category("Refactorings")]
178+
public void MoveToFolderRefactoring_TargetNotAModule_Throws()
179+
{
180+
const string code = @"
181+
Public Sub Foo()
182+
End Sub
183+
";
184+
Func<MoveMultipleToFolderModel, MoveMultipleToFolderModel> presenterAction = (model) =>
185+
{
186+
model.TargetFolder = "MyNewFolder.MySubFolder";
187+
return model;
188+
};
189+
190+
var refactoredCode = RefactoredCode(
191+
"Foo",
192+
DeclarationType.Procedure,
193+
presenterAction,
194+
typeof(InvalidDeclarationTypeException),
195+
("TestModule", code, ComponentType.StandardModule));
196+
}
197+
198+
199+
protected override IRefactoring TestRefactoring(
200+
IRewritingManager rewritingManager,
201+
RubberduckParserState state,
202+
IRefactoringPresenterFactory factory,
203+
ISelectionService selectionService)
204+
{
205+
var uiDispatcherMock = new Mock<IUiDispatcher>();
206+
uiDispatcherMock
207+
.Setup(m => m.Invoke(It.IsAny<Action>()))
208+
.Callback((Action action) => action.Invoke());
209+
210+
var annotationUpdater = new AnnotationUpdater();
211+
var moveToFolderAction = new MoveToFolderRefactoringAction(rewritingManager, annotationUpdater);
212+
var moveMultipleToFolderAction = new MoveMultipleToFolderRefactoringAction(rewritingManager, moveToFolderAction);
213+
214+
var selectedDeclarationProvider = new SelectedDeclarationProvider(selectionService, state);
215+
return new MoveToFolderRefactoring(moveMultipleToFolderAction, selectedDeclarationProvider, selectionService, factory, uiDispatcherMock.Object, state);
216+
}
217+
}
218+
}

0 commit comments

Comments
 (0)