Skip to content

Commit 8cfab14

Browse files
committed
More unit tests
1 parent c7a813c commit 8cfab14

File tree

10 files changed

+585
-118
lines changed

10 files changed

+585
-118
lines changed

RetailCoder.VBE/UI/Command/AddTestModuleCommand.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using System.Runtime.InteropServices;
22
using Microsoft.Vbe.Interop;
33
using NLog;
4-
using Rubberduck.Parsing.VBA;
54
using Rubberduck.UnitTesting;
65
using Rubberduck.VBEditor.Extensions;
76

@@ -16,7 +15,7 @@ public class AddTestModuleCommand : CommandBase
1615
private readonly VBE _vbe;
1716
private readonly NewUnitTestModuleCommand _command;
1817

19-
public AddTestModuleCommand(VBE vbe, RubberduckParserState state, NewUnitTestModuleCommand command) : base(LogManager.GetCurrentClassLogger())
18+
public AddTestModuleCommand(VBE vbe, NewUnitTestModuleCommand command) : base(LogManager.GetCurrentClassLogger())
2019
{
2120
_vbe = vbe;
2221
_command = command;

RetailCoder.VBE/UI/UnitTesting/TestExplorerViewModel.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ public TestExplorerViewModel(VBE vbe,
5151
_runAllTestsCommand = new RunAllTestsCommand(vbe, state, testEngine, model);
5252
_runAllTestsCommand.RunCompleted += RunCompleted;
5353

54-
_addTestModuleCommand = new AddTestModuleCommand(vbe, state, newTestModuleCommand);
54+
_addTestModuleCommand = new AddTestModuleCommand(vbe, newTestModuleCommand);
5555
_addTestMethodCommand = new AddTestMethodCommand(vbe, state, newTestMethodCommand);
5656
_addErrorTestMethodCommand = new AddTestMethodExpectedErrorCommand(vbe, state, newTestMethodCommand);
5757

RetailCoder.VBE/UnitTesting/NewUnitTestModuleCommand.cs

Lines changed: 21 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -19,32 +19,32 @@ public NewUnitTestModuleCommand(RubberduckParserState state, ConfigurationLoader
1919
_configLoader = configLoader;
2020
}
2121

22-
private const string ModuleLateBinding = "Private Assert As Object\n";
23-
private const string ModuleEarlyBinding = "Private Assert As New Rubberduck.{0}AssertClass\n";
22+
private const string ModuleLateBinding = "Private Assert As Object\r\n";
23+
private const string ModuleEarlyBinding = "Private Assert As New Rubberduck.{0}AssertClass\r\n";
2424

25-
private const string TestModuleEmptyTemplate = "'@TestModule\n{0}\n";
25+
private const string TestModuleEmptyTemplate = "'@TestModule\r\n{0}\r\n";
2626

27-
private const string ModuleInitLateBinding = "Set Assert = CreateObject(\"Rubberduck.{0}AssertClass\")\n";
27+
private const string ModuleInitLateBinding = "Set Assert = CreateObject(\"Rubberduck.{0}AssertClass\")\r\n";
2828
private readonly string _moduleInit = string.Concat(
29-
"'@ModuleInitialize\n"
30-
, "Public Sub ModuleInitialize()\n"
31-
, " '", RubberduckUI.UnitTest_NewModule_RunOnce, ".\n {0}\n"
32-
, "End Sub\n\n"
33-
, "'@ModuleCleanup\n"
34-
, "Public Sub ModuleCleanup()\n"
35-
, " '", RubberduckUI.UnitTest_NewModule_RunOnce, ".\n"
36-
, "End Sub\n\n"
29+
"'@ModuleInitialize\r\n"
30+
, "Public Sub ModuleInitialize()\r\n"
31+
, " '", RubberduckUI.UnitTest_NewModule_RunOnce, ".\r\n {0}\r\n"
32+
, "End Sub\r\n\r\n"
33+
, "'@ModuleCleanup\r\n"
34+
, "Public Sub ModuleCleanup()\r\n"
35+
, " '", RubberduckUI.UnitTest_NewModule_RunOnce, ".\r\n"
36+
, "End Sub\r\n\r\n"
3737
);
3838

3939
private readonly string _methodInit = string.Concat(
40-
"'@TestInitialize\n"
41-
, "Public Sub TestInitialize()\n"
42-
, " '", RubberduckUI.UnitTest_NewModule_RunBeforeTest, ".\n"
43-
, "End Sub\n\n"
44-
, "'@TestCleanup\n"
45-
, "Public Sub TestCleanup()\n"
46-
, " '", RubberduckUI.UnitTest_NewModule_RunAfterTest, ".\n"
47-
, "End Sub\n\n"
40+
"'@TestInitialize\r\n"
41+
, "Public Sub TestInitialize()\r\n"
42+
, " '", RubberduckUI.UnitTest_NewModule_RunBeforeTest, ".\r\n"
43+
, "End Sub\r\n\r\n"
44+
, "'@TestCleanup\r\n"
45+
, "Public Sub TestCleanup()\r\n"
46+
, " '", RubberduckUI.UnitTest_NewModule_RunAfterTest, ".\r\n"
47+
, "End Sub\r\n\r\n"
4848
);
4949

5050
private const string TestModuleBaseName = "TestModule";
@@ -95,7 +95,7 @@ public void NewUnitTestModule(VBProject project)
9595
hasOptionExplicit = component.CodeModule.Lines[1, component.CodeModule.CountOfDeclarationLines].Contains("Option Explicit");
9696
}
9797

98-
var options = string.Concat(hasOptionExplicit ? string.Empty : "Option Explicit\n", "Option Private Module\n\n");
98+
var options = string.Concat(hasOptionExplicit ? string.Empty : "Option Explicit\r\n", "Option Private Module\r\n\r\n");
9999

100100
var defaultTestMethod = string.Empty;
101101
if (settings.DefaultTestStubInNewModule)

RubberduckTests/Commands/AddTestMethodCommandTests.cs

Lines changed: 0 additions & 88 deletions
This file was deleted.

RubberduckTests/FindCommands/FindAllImplementationsTests.cs renamed to RubberduckTests/Commands/FindAllImplementationsTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@
1313
using Rubberduck.VBEditor.VBEHost;
1414
using RubberduckTests.Mocks;
1515

16-
namespace RubberduckTests.FindCommands
16+
namespace RubberduckTests.Commands
1717
{
1818
[TestClass]
1919
public class FindAllImplementationsTests

RubberduckTests/FindCommands/FindAllReferencesTests.cs renamed to RubberduckTests/Commands/FindAllReferencesTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@
1313
using Rubberduck.VBEditor.VBEHost;
1414
using RubberduckTests.Mocks;
1515

16-
namespace RubberduckTests.FindCommands
16+
namespace RubberduckTests.Commands
1717
{
1818
[TestClass]
1919
public class FindAllReferencesTests
Lines changed: 201 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,201 @@
1+
using System.Threading;
2+
using Microsoft.Vbe.Interop;
3+
using Microsoft.VisualStudio.TestTools.UnitTesting;
4+
using Moq;
5+
using Rubberduck.Parsing;
6+
using Rubberduck.Parsing.VBA;
7+
using Rubberduck.SmartIndenter;
8+
using Rubberduck.UI.Command;
9+
using Rubberduck.VBEditor.Extensions;
10+
using Rubberduck.VBEditor.VBEHost;
11+
using RubberduckTests.Mocks;
12+
13+
namespace RubberduckTests.Commands
14+
{
15+
[TestClass]
16+
public class IndentCommandTests
17+
{
18+
[TestMethod]
19+
public void AddNoIndentAnnotation()
20+
{
21+
var builder = new MockVbeBuilder();
22+
VBComponent component;
23+
var vbe = builder.BuildFromSingleStandardModule("", out component);
24+
var mockHost = new Mock<IHostApplication>();
25+
mockHost.SetupAllProperties();
26+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
27+
28+
parser.Parse(new CancellationTokenSource());
29+
if (parser.State.Status >= ParserState.Error)
30+
{
31+
Assert.Inconclusive("Parser Error");
32+
}
33+
34+
var noIndentAnnotationCommand = new NoIndentAnnotationCommand(vbe.Object, parser.State);
35+
noIndentAnnotationCommand.Execute(null);
36+
37+
Assert.AreEqual("'@NoIndent\r\n", component.CodeModule.Lines());
38+
}
39+
40+
[TestMethod]
41+
public void AddNoIndentAnnotation_ModuleContainsCode()
42+
{
43+
var input =
44+
@"Option Explicit
45+
Public Foo As Boolean
46+
47+
Sub Foo()
48+
End Sub";
49+
50+
var expected =
51+
@"'@NoIndent
52+
Option Explicit
53+
Public Foo As Boolean
54+
55+
Sub Foo()
56+
End Sub";
57+
58+
var builder = new MockVbeBuilder();
59+
VBComponent component;
60+
var vbe = builder.BuildFromSingleStandardModule(input, out component);
61+
var mockHost = new Mock<IHostApplication>();
62+
mockHost.SetupAllProperties();
63+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
64+
65+
parser.Parse(new CancellationTokenSource());
66+
if (parser.State.Status >= ParserState.Error)
67+
{
68+
Assert.Inconclusive("Parser Error");
69+
}
70+
71+
var noIndentAnnotationCommand = new NoIndentAnnotationCommand(vbe.Object, parser.State);
72+
noIndentAnnotationCommand.Execute(null);
73+
74+
Assert.AreEqual(expected, component.CodeModule.Lines());
75+
}
76+
77+
[TestMethod]
78+
public void AddNoIndentAnnotation_CanExecute_NullActiveCodePane()
79+
{
80+
var builder = new MockVbeBuilder();
81+
VBComponent component;
82+
var vbe = builder.BuildFromSingleStandardModule("", out component);
83+
vbe.Setup(v => v.ActiveCodePane).Returns((CodePane) null);
84+
var mockHost = new Mock<IHostApplication>();
85+
mockHost.SetupAllProperties();
86+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
87+
88+
parser.Parse(new CancellationTokenSource());
89+
if (parser.State.Status >= ParserState.Error)
90+
{
91+
Assert.Inconclusive("Parser Error");
92+
}
93+
94+
var noIndentAnnotationCommand = new NoIndentAnnotationCommand(vbe.Object, parser.State);
95+
Assert.IsFalse(noIndentAnnotationCommand.CanExecute(null));
96+
}
97+
98+
[TestMethod]
99+
public void AddNoIndentAnnotation_CanExecute_ModuleAlreadyHasAnnotation()
100+
{
101+
var builder = new MockVbeBuilder();
102+
VBComponent component;
103+
var vbe = builder.BuildFromSingleStandardModule("'@NoIndent\r\n", out component);
104+
vbe.Setup(v => v.ActiveCodePane).Returns((CodePane)null);
105+
var mockHost = new Mock<IHostApplication>();
106+
mockHost.SetupAllProperties();
107+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
108+
109+
parser.Parse(new CancellationTokenSource());
110+
if (parser.State.Status >= ParserState.Error)
111+
{
112+
Assert.Inconclusive("Parser Error");
113+
}
114+
115+
var noIndentAnnotationCommand = new NoIndentAnnotationCommand(vbe.Object, parser.State);
116+
Assert.IsFalse(noIndentAnnotationCommand.CanExecute(null));
117+
}
118+
119+
[TestMethod]
120+
public void IndentModule_IndentsModule()
121+
{
122+
var input =
123+
@" Option Explicit ' at least I used it...
124+
Sub InverseIndent()
125+
Dim d As Boolean
126+
Dim s As Integer
127+
128+
End Sub
129+
130+
Sub RandomIndent()
131+
Dim d As Boolean
132+
Dim s As Integer
133+
134+
End Sub
135+
";
136+
137+
var expected =
138+
@"Option Explicit ' at least I used it...
139+
Sub InverseIndent()
140+
Dim d As Boolean
141+
Dim s As Integer
142+
143+
End Sub
144+
145+
Sub RandomIndent()
146+
Dim d As Boolean
147+
Dim s As Integer
148+
149+
End Sub
150+
";
151+
152+
var builder = new MockVbeBuilder();
153+
var project = builder.ProjectBuilder("Proj1", vbext_ProjectProtection.vbext_pp_none)
154+
.AddComponent("Comp1", vbext_ComponentType.vbext_ct_ClassModule, input)
155+
.AddComponent("Comp2", vbext_ComponentType.vbext_ct_ClassModule, input)
156+
.Build();
157+
158+
var vbe = builder.AddProject(project).Build();
159+
vbe.Setup(s => s.ActiveCodePane).Returns(project.Object.VBComponents.Item("Comp2").CodeModule.CodePane);
160+
161+
var mockHost = new Mock<IHostApplication>();
162+
mockHost.SetupAllProperties();
163+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
164+
165+
parser.Parse(new CancellationTokenSource());
166+
if (parser.State.Status >= ParserState.Error)
167+
{
168+
Assert.Inconclusive("Parser Error");
169+
}
170+
171+
var indentCommand = new IndentCurrentModuleCommand(vbe.Object, CreateIndenter(vbe.Object));
172+
indentCommand.Execute(null);
173+
174+
Assert.AreEqual(input, project.Object.VBComponents.Item("Comp1").CodeModule.Lines());
175+
Assert.AreEqual(expected, project.Object.VBComponents.Item("Comp2").CodeModule.Lines());
176+
}
177+
178+
private static IIndenter CreateIndenter(VBE vbe)
179+
{
180+
var settings = new Mock<IndenterSettings>();
181+
settings.Setup(s => s.IndentEntireProcedureBody).Returns(true);
182+
settings.Setup(s => s.IndentFirstCommentBlock).Returns(true);
183+
settings.Setup(s => s.IndentFirstDeclarationBlock).Returns(true);
184+
settings.Setup(s => s.AlignCommentsWithCode).Returns(true);
185+
settings.Setup(s => s.AlignContinuations).Returns(true);
186+
settings.Setup(s => s.IgnoreOperatorsInContinuations).Returns(true);
187+
settings.Setup(s => s.IndentCase).Returns(false);
188+
settings.Setup(s => s.ForceDebugStatementsInColumn1).Returns(false);
189+
settings.Setup(s => s.ForceCompilerDirectivesInColumn1).Returns(false);
190+
settings.Setup(s => s.IndentCompilerDirectives).Returns(true);
191+
settings.Setup(s => s.AlignDims).Returns(false);
192+
settings.Setup(s => s.AlignDimColumn).Returns(15);
193+
settings.Setup(s => s.EnableUndo).Returns(true);
194+
settings.Setup(s => s.EndOfLineCommentStyle).Returns(EndOfLineCommentStyle.AlignInColumn);
195+
settings.Setup(s => s.EndOfLineCommentColumnSpaceAlignment).Returns(50);
196+
settings.Setup(s => s.IndentSpaces).Returns(4);
197+
198+
return new Indenter(vbe, () => new IndenterSettings());
199+
}
200+
}
201+
}

0 commit comments

Comments
 (0)