Skip to content

Commit dae8848

Browse files
committed
added red/repro tests for #4531
1 parent 18d1cc7 commit dae8848

File tree

2 files changed

+65
-4
lines changed

2 files changed

+65
-4
lines changed

RubberduckTests/Mocks/MockVbeBuilder.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -127,22 +127,22 @@ public Mock<IVBE> Build()
127127
/// <param name="selection">Specifies user selection in the editor.</param>
128128
/// <param name="referenceStdLibs">Specifies whether standard libraries are referenced.</param>
129129
/// <returns></returns>
130-
public static Mock<IVBE> BuildFromSingleStandardModule(string content, out IVBComponent component, Selection selection = default(Selection), bool referenceStdLibs = false)
130+
public static Mock<IVBE> BuildFromSingleStandardModule(string content, out IVBComponent component, Selection selection = default, bool referenceStdLibs = false)
131131
{
132132
return BuildFromSingleModule(content, TestModuleName, ComponentType.StandardModule, out component, selection, referenceStdLibs);
133133
}
134134

135-
public static Mock<IVBE> BuildFromSingleStandardModule(string content, string name, out IVBComponent component, Selection selection = default(Selection), bool referenceStdLibs = false)
135+
public static Mock<IVBE> BuildFromSingleStandardModule(string content, string name, out IVBComponent component, Selection selection = default, bool referenceStdLibs = false)
136136
{
137137
return BuildFromSingleModule(content, name, ComponentType.StandardModule, out component, selection, referenceStdLibs);
138138
}
139139

140-
public static Mock<IVBE> BuildFromSingleModule(string content, ComponentType type, out IVBComponent component, Selection selection = default(Selection), bool referenceStdLibs = false)
140+
public static Mock<IVBE> BuildFromSingleModule(string content, ComponentType type, out IVBComponent component, Selection selection = default, bool referenceStdLibs = false)
141141
{
142142
return BuildFromSingleModule(content, TestModuleName, type, out component, selection, referenceStdLibs);
143143
}
144144

145-
public static Mock<IVBE> BuildFromSingleModule(string content, string name, ComponentType type, out IVBComponent component, Selection selection = default(Selection), bool referenceStdLibs = false)
145+
public static Mock<IVBE> BuildFromSingleModule(string content, string name, ComponentType type, out IVBComponent component, Selection selection = default, bool referenceStdLibs = false)
146146
{
147147
var vbeBuilder = new MockVbeBuilder();
148148

RubberduckTests/QuickFixes/UseSetKeywordForObjectAssignmentQuickFixTests.cs

Lines changed: 61 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,12 +3,59 @@
33
using Rubberduck.Inspections.QuickFixes;
44
using Rubberduck.Parsing.Inspections.Abstract;
55
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.VBEditor.SafeComWrappers;
7+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
8+
using RubberduckTests.Mocks;
69

710
namespace RubberduckTests.QuickFixes
811
{
912
[TestFixture]
1013
public class UseSetKeywordForObjectAssignmentQuickFixTests : QuickFixTestBase
1114
{
15+
[Test]
16+
[Category("QuickFixes")]
17+
public void ObjectVariableNotSet_ReplacesExplicitLetKeyword()
18+
{
19+
var inputCode = @"
20+
Private Sub TextBox1_Change()
21+
Dim foo As Range
22+
Set foo = Range(""A1"")
23+
Let foo.Font = Range(""B1"").Font
24+
End Sub
25+
";
26+
var expectedCode = @"
27+
Private Sub TextBox1_Change()
28+
Dim foo As Range
29+
Set foo = Range(""A1"")
30+
Set foo.Font = Range(""B1"").Font
31+
End Sub
32+
";
33+
var actualCode = ApplyQuickFixToAllInspectionResults(inputCode, state => new ObjectVariableNotSetInspection(state));
34+
Assert.AreEqual(expectedCode, actualCode);
35+
}
36+
37+
[Test]
38+
[Category("QuickFixes")]
39+
public void ObjectVariableNotSet_PlacesKeywordBeforeMemberCall()
40+
{
41+
var inputCode = @"
42+
Private Sub TextBox1_Change()
43+
Dim foo As Range
44+
Set foo = Range(""A1"")
45+
foo.Font = Range(""B1"").Font
46+
End Sub
47+
";
48+
var expectedCode = @"
49+
Private Sub TextBox1_Change()
50+
Dim foo As Range
51+
Set foo = Range(""A1"")
52+
Set foo.Font = Range(""B1"").Font
53+
End Sub
54+
";
55+
var actualCode = ApplyQuickFixToAllInspectionResults(inputCode, state => new ObjectVariableNotSetInspection(state));
56+
Assert.AreEqual(expectedCode, actualCode);
57+
}
58+
1259
[Test]
1360
[Category("QuickFixes")]
1461
public void ObjectVariableNotSet_ForFunctionAssignment_ReturnsResult()
@@ -63,5 +110,19 @@ protected override IQuickFix QuickFix(RubberduckParserState state)
63110
{
64111
return new UseSetKeywordForObjectAssignmentQuickFix();
65112
}
113+
114+
protected override IVBE TestVbe(string code, out IVBComponent component)
115+
{
116+
var builder = new MockVbeBuilder();
117+
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
118+
.AddComponent("Module1", ComponentType.StandardModule, code)
119+
.AddReference("Excel", MockVbeBuilder.LibraryPathMsExcel, 1, 8, true)
120+
.Build();
121+
122+
var vbe = builder.AddProject(project).Build().Object;
123+
component = project.Object.VBComponents[0];
124+
return vbe;
125+
}
126+
66127
}
67128
}

0 commit comments

Comments
 (0)