Skip to content

Commit c6ec12b

Browse files
committed
Improve test coverage of refactor rename regarding input validation
1 parent c7cc8f0 commit c6ec12b

File tree

5 files changed

+129
-8
lines changed

5 files changed

+129
-8
lines changed

Rubberduck.Refactorings/Rename/RenameRefactoring.cs

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

5252
protected override RenameModel InitializeModel(Declaration target)
5353
{
54-
if (target == null)
55-
{
56-
throw new TargetDeclarationIsNullException();
57-
}
58-
5954
CheckWhetherValidTarget(target);
6055

6156
var model = DeriveTarget(new RenameModel(target));

RubberduckTests/Refactoring/ImplementInterfaceTests.cs

Lines changed: 33 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,18 +1,51 @@
1+
using System;
2+
using System.Linq;
13
using NUnit.Framework;
24
using Rubberduck.Parsing.Rewriter;
5+
using Rubberduck.Parsing.Symbols;
36
using Rubberduck.Parsing.VBA;
47
using Rubberduck.Refactorings;
58
using Rubberduck.Refactorings.Exceptions.ImplementInterface;
69
using Rubberduck.Refactorings.ImplementInterface;
710
using Rubberduck.VBEditor;
811
using Rubberduck.VBEditor.SafeComWrappers;
912
using Rubberduck.VBEditor.Utility;
13+
using RubberduckTests.Mocks;
1014

1115
namespace RubberduckTests.Refactoring
1216
{
1317
[TestFixture]
1418
public class ImplementInterfaceTests : RefactoringTestBase
1519
{
20+
[Test]
21+
[Category("Refactorings")]
22+
[Category("Implement Interface")]
23+
public override void TargetNull_Throws()
24+
{
25+
var testVbe = TestVbe(string.Empty, out _);
26+
var (state, rewritingManager) = MockParser.CreateAndParseWithRewritingManager(testVbe);
27+
using (state)
28+
{
29+
var refactoring = TestRefactoring(rewritingManager, state);
30+
Assert.Throws<NotSupportedException>(() => refactoring.Refactor((Declaration)null));
31+
}
32+
}
33+
34+
[Test]
35+
[Category("Refactorings")]
36+
[Category("Implement Interface")]
37+
public void DoesNotSupportCallingWithADeclaration()
38+
{
39+
var testVbe = TestVbe(("testClass", string.Empty, ComponentType.ClassModule));
40+
var (state, rewritingManager) = MockParser.CreateAndParseWithRewritingManager(testVbe);
41+
using (state)
42+
{
43+
var target = state.DeclarationFinder.UserDeclarations(DeclarationType.ClassModule).Single();
44+
var refactoring = TestRefactoring(rewritingManager, state);
45+
Assert.Throws<NotSupportedException>(() => refactoring.Refactor(target));
46+
}
47+
}
48+
1649
[Test]
1750
[Category("Refactorings")]
1851
[Category("Implement Interface")]

RubberduckTests/Refactoring/InteractiveRefactoringTestBase.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -97,7 +97,7 @@ protected IDictionary<string, string> RefactoredCode(IVBE vbe, string declaratio
9797
var (state, rewritingManager) = MockParser.CreateAndParseWithRewritingManager(vbe);
9898
using (state)
9999
{
100-
var target = state.DeclarationFinder.UserDeclarations(declarationType)
100+
var target = state.DeclarationFinder.DeclarationsWithType(declarationType)
101101
.Single(declaration => declaration.IdentifierName == declarationName);
102102

103103
var refactoring = TestRefactoring(rewritingManager, state, presenterAdjustment);

RubberduckTests/Refactoring/RefactoringTestBase.cs

Lines changed: 14 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,6 @@ public abstract class RefactoringTestBase
2121
{
2222
[Test]
2323
[Category("Refactorings")]
24-
[Category("Introduce Field")]
2524
public void NoActiveSelection_Throws()
2625
{
2726
var rewritingManager = new Mock<IRewritingManager>().Object;
@@ -30,6 +29,19 @@ public void NoActiveSelection_Throws()
3029
Assert.Throws<NoActiveSelectionException>(() => refactoring.Refactor());
3130
}
3231

32+
[Test]
33+
[Category("Refactorings")]
34+
public virtual void TargetNull_Throws()
35+
{
36+
var testVbe = TestVbe(string.Empty, out _);
37+
var (state, rewritingManager) = MockParser.CreateAndParseWithRewritingManager(testVbe);
38+
using (state)
39+
{
40+
var refactoring = TestRefactoring(rewritingManager, state);
41+
Assert.Throws<TargetDeclarationIsNullException>(() => refactoring.Refactor((Declaration)null));
42+
}
43+
}
44+
3345
protected string RefactoredCode(string code, Selection selection, Type expectedException = null, bool executeViaActiveSelection = false)
3446
{
3547
var vbe = TestVbe(code, out _);
@@ -49,7 +61,7 @@ protected IDictionary<string, string> RefactoredCode(IVBE vbe, string selectedCo
4961
var (state, rewritingManager) = MockParser.CreateAndParseWithRewritingManager(vbe);
5062
using (state)
5163
{
52-
var module = state.DeclarationFinder.UserDeclarations(DeclarationType.Module)
64+
var module = state.DeclarationFinder.DeclarationsWithType(DeclarationType.Module)
5365
.Single(declaration => declaration.IdentifierName == selectedComponentName)
5466
.QualifiedModuleName;
5567
var qualifiedSelection = new QualifiedSelection(module, selection);

RubberduckTests/Refactoring/Rename/RenameTests.cs

Lines changed: 81 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@
1616
using Rubberduck.Parsing.VBA;
1717
using Rubberduck.Refactorings;
1818
using Rubberduck.Refactorings.Exceptions;
19+
using Rubberduck.Refactorings.Exceptions.Rename;
1920
using Rubberduck.UI.Refactorings;
2021
using Rubberduck.VBEditor.Utility;
2122

@@ -2646,6 +2647,86 @@ public void Rename_PresenterIsNull()
26462647
Assert.AreEqual(inputCode, actualCode);
26472648
}
26482649
}
2650+
2651+
[Category("Refactorings")]
2652+
[Category("Rename")]
2653+
[TestCase("Class_Initialize")]
2654+
[TestCase("Class_Terminate")]
2655+
public void Rename_StandardEventHandler(string handlerName)
2656+
{
2657+
var inputCode =
2658+
$@"Private Sub {handlerName}()
2659+
End Sub";
2660+
2661+
var presenterAction = AdjustName("test");
2662+
2663+
var actualCode = RefactoredCode(
2664+
handlerName,
2665+
DeclarationType.Procedure,
2666+
presenterAction,
2667+
typeof(TargetDeclarationIsStandardEventHandlerException),
2668+
("TestClass", inputCode, ComponentType.ClassModule));
2669+
Assert.AreEqual(inputCode, actualCode["TestClass"]);
2670+
}
2671+
2672+
[Test]
2673+
[Category("Refactorings")]
2674+
[Category("Rename")]
2675+
public void Rename_NotUserDefined()
2676+
{
2677+
const string inputCode =
2678+
@"Private Sub Foo()
2679+
Dim bar As Color|ScaleCriteria
2680+
End Sub";
2681+
2682+
var tdo = new RenameTestsDataObject(declarationName: "ColorScaleCriteria", newName: "Goo", declarationType: DeclarationType.ClassModule);
2683+
var inputOutput1 = new RenameTestModuleDefinition("Class1")
2684+
{
2685+
Input = inputCode,
2686+
Expected = inputCode.Replace("|", string.Empty)
2687+
};
2688+
tdo.UseLibraries = true;
2689+
tdo.ExpectedException = typeof(TargetDeclarationNotUserDefinedException);
2690+
2691+
PerformExpectedVersusActualRenameTests(tdo, inputOutput1);
2692+
}
2693+
2694+
[Test]
2695+
[Category("Refactorings")]
2696+
[Category("Rename")]
2697+
[Ignore("Something is off with the project id of the implemented class: it does not agree with the project id of the exposing library.")]
2698+
public void Rename_ImplementedInterfaceNotUserDefined()
2699+
{
2700+
var inputCode =
2701+
@"Implements PivotFields
2702+
2703+
Private Property Get Pivo|tFields_Count() As Long
2704+
End Property
2705+
2706+
Private Function PivotFields_Item(Index) As Object
2707+
End Function
2708+
2709+
Private Property Get PivotFields_Application() As Application
2710+
End Property
2711+
2712+
Private Property Get PivotFields_Creator() As XlCreator
2713+
End Property
2714+
2715+
Private Property Get PivotFields_Parent() As PivotTable
2716+
End Property
2717+
";
2718+
2719+
var tdo = new RenameTestsDataObject(declarationName: "PivotFields_Count", newName: "Goo", declarationType: DeclarationType.PropertyGet);
2720+
var inputOutput1 = new RenameTestModuleDefinition("Class1")
2721+
{
2722+
Input = inputCode,
2723+
Expected = inputCode.Replace("|", string.Empty)
2724+
};
2725+
tdo.UseLibraries = true;
2726+
tdo.ExpectedException = typeof(TargetDeclarationNotUserDefinedException);
2727+
2728+
PerformExpectedVersusActualRenameTests(tdo, inputOutput1);
2729+
}
26492730

26502731
[Test]
26512732
[Category("Refactorings")]

0 commit comments

Comments
 (0)