Skip to content

Commit ac88973

Browse files
authored
Merge pull request #2134 from Hosch250/unitTests
Unit tests
2 parents 7055b17 + 817e2ff commit ac88973

18 files changed

+843
-309
lines changed

RetailCoder.VBE/Root/RubberduckModule.cs

Lines changed: 4 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,6 @@
2727
using Rubberduck.UI.SourceControl;
2828
using Rubberduck.UI.ToDoItems;
2929
using Rubberduck.UI.UnitTesting;
30-
using Rubberduck.UnitTesting;
3130
using Rubberduck.VBEditor.VBEHost;
3231
using Rubberduck.Parsing.Preprocessing;
3332
using System.Globalization;
@@ -63,8 +62,6 @@ public override void Load()
6362
Bind<App>().ToSelf().InSingletonScope();
6463
Bind<RubberduckParserState>().ToSelf().InSingletonScope();
6564
Bind<GitProvider>().ToSelf().InSingletonScope();
66-
Bind<NewUnitTestModuleCommand>().ToSelf().InSingletonScope();
67-
Bind<NewTestMethodCommand>().ToSelf().InSingletonScope();
6865
Bind<RubberduckCommandBar>().ToSelf().InSingletonScope();
6966
Bind<TestExplorerModel>().ToSelf().InSingletonScope();
7067
Bind<IOperatingSystem>().To<WindowsOperatingSystem>().InSingletonScope();
@@ -107,10 +104,10 @@ public override void Load()
107104
.InSingletonScope()
108105
.WithConstructorArgument<IDockableUserControl>(new CodeInspectionsWindow { ViewModel = Kernel.Get<InspectionResultsViewModel>() });
109106

110-
Bind<IControlView>().To<ChangesView>().Named("changesView");
111-
Bind<IControlView>().To<BranchesView>().Named("branchesView");
112-
Bind<IControlView>().To<UnsyncedCommitsView>().Named("unsyncedCommitsView");
113-
Bind<IControlView>().To<SettingsView>().Named("settingsView");
107+
Bind<IControlView>().To<ChangesView>();
108+
Bind<IControlView>().To<BranchesView>();
109+
Bind<IControlView>().To<UnsyncedCommitsView>();
110+
Bind<IControlView>().To<SettingsView>();
114111

115112
Bind<IControlViewModel>().To<ChangesViewViewModel>()
116113
.WhenInjectedInto<ChangesView>();

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -952,8 +952,6 @@
952952
<Compile Include="UnitTesting\IAssert.cs" />
953953
<Compile Include="UnitTesting\ITestEngine.cs" />
954954
<Compile Include="UnitTesting\ITestRunner.cs" />
955-
<Compile Include="UnitTesting\NewTestMethodCommand.cs" />
956-
<Compile Include="UnitTesting\NewUnitTestModuleCommand.cs" />
957955
<Compile Include="UnitTesting\ProjectTestExtensions.cs" />
958956
<Compile Include="UnitTesting\TestEngine.cs" />
959957
<Compile Include="UnitTesting\TestMethod.cs" />

RetailCoder.VBE/UI/CodeExplorer/Commands/AddTestModuleCommand.cs

Lines changed: 5 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -4,17 +4,16 @@
44
using Rubberduck.Navigation.CodeExplorer;
55
using Rubberduck.Parsing.Symbols;
66
using Rubberduck.UI.Command;
7-
using Rubberduck.UnitTesting;
87

98
namespace Rubberduck.UI.CodeExplorer.Commands
109
{
1110
[CodeExplorerCommand]
1211
public class AddTestModuleCommand : CommandBase
1312
{
1413
private readonly VBE _vbe;
15-
private readonly NewUnitTestModuleCommand _newUnitTestModuleCommand;
14+
private readonly Command.AddTestModuleCommand _newUnitTestModuleCommand;
1615

17-
public AddTestModuleCommand(VBE vbe, NewUnitTestModuleCommand newUnitTestModuleCommand) : base(LogManager.GetCurrentClassLogger())
16+
public AddTestModuleCommand(VBE vbe, Command.AddTestModuleCommand newUnitTestModuleCommand) : base(LogManager.GetCurrentClassLogger())
1817
{
1918
_vbe = vbe;
2019
_newUnitTestModuleCommand = newUnitTestModuleCommand;
@@ -34,14 +33,9 @@ protected override bool CanExecuteImpl(object parameter)
3433

3534
protected override void ExecuteImpl(object parameter)
3635
{
37-
if (parameter != null)
38-
{
39-
_newUnitTestModuleCommand.NewUnitTestModule(GetDeclaration(parameter).Project);
40-
}
41-
else
42-
{
43-
_newUnitTestModuleCommand.NewUnitTestModule(_vbe.VBProjects.Item(1));
44-
}
36+
_newUnitTestModuleCommand.Execute(parameter != null
37+
? GetDeclaration(parameter).Project
38+
: _vbe.VBProjects.Item(1));
4539
}
4640

4741
private Declaration GetDeclaration(object parameter)

RetailCoder.VBE/UI/Command/AddTestMethodCommand.cs

Lines changed: 49 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -16,19 +16,36 @@ namespace Rubberduck.UI.Command
1616
public class AddTestMethodCommand : CommandBase
1717
{
1818
private readonly VBE _vbe;
19-
private readonly NewTestMethodCommand _command;
2019
private readonly RubberduckParserState _state;
2120

22-
public AddTestMethodCommand(VBE vbe, RubberduckParserState state, NewTestMethodCommand command) : base(LogManager.GetCurrentClassLogger())
21+
public AddTestMethodCommand(VBE vbe, RubberduckParserState state) : base(LogManager.GetCurrentClassLogger())
2322
{
2423
_vbe = vbe;
25-
_command = command;
2624
_state = state;
2725
}
2826

27+
public const string NamePlaceholder = "%METHODNAME%";
28+
private const string TestMethodBaseName = "TestMethod";
29+
30+
public static readonly string TestMethodTemplate = string.Concat(
31+
"'@TestMethod\r\n",
32+
"Public Sub ", NamePlaceholder, "() 'TODO ", RubberduckUI.UnitTest_NewMethod_Rename, "\r\n",
33+
" On Error GoTo TestFail\r\n",
34+
" \r\n",
35+
" 'Arrange:\r\n\r\n",
36+
" 'Act:\r\n\r\n",
37+
" 'Assert:\r\n",
38+
" Assert.Inconclusive\r\n\r\n",
39+
"TestExit:\r\n",
40+
" Exit Sub\r\n",
41+
"TestFail:\r\n",
42+
" Assert.Fail \"", RubberduckUI.UnitTest_NewMethod_RaisedTestError, ": #\" & Err.Number & \" - \" & Err.Description\r\n",
43+
"End Sub\r\n"
44+
);
45+
2946
protected override bool CanExecuteImpl(object parameter)
3047
{
31-
if (_state.Status != ParserState.Ready) { return false; }
48+
if (_state.Status != ParserState.Ready || _vbe.ActiveCodePane == null) { return false; }
3249

3350
var testModules = _state.AllUserDeclarations.Where(d =>
3451
d.DeclarationType == DeclarationType.ProceduralModule &&
@@ -49,7 +66,34 @@ protected override bool CanExecuteImpl(object parameter)
4966

5067
protected override void ExecuteImpl(object parameter)
5168
{
52-
_command.NewTestMethod();
69+
if (_vbe.ActiveCodePane == null) { return; }
70+
71+
try
72+
{
73+
var declaration = _state.GetTestModules().FirstOrDefault(f =>
74+
f.QualifiedName.QualifiedModuleName.Component.CodeModule == _vbe.ActiveCodePane.CodeModule);
75+
76+
if (declaration != null)
77+
{
78+
var module = _vbe.ActiveCodePane.CodeModule;
79+
var name = GetNextTestMethodName(module.Parent);
80+
var body = TestMethodTemplate.Replace(NamePlaceholder, name);
81+
module.InsertLines(module.CountOfLines, body);
82+
}
83+
}
84+
catch (COMException)
85+
{
86+
}
87+
88+
_state.OnParseRequested(this, _vbe.SelectedVBComponent);
89+
}
90+
91+
private string GetNextTestMethodName(VBComponent component)
92+
{
93+
var names = component.GetTests(_vbe, _state).Select(test => test.Declaration.IdentifierName);
94+
var index = names.Count(n => n.StartsWith(TestMethodBaseName)) + 1;
95+
96+
return string.Concat(TestMethodBaseName, index);
5397
}
5498
}
5599
}

RetailCoder.VBE/UI/Command/AddTestMethodExpectedErrorCommand.cs

Lines changed: 54 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -16,19 +16,41 @@ namespace Rubberduck.UI.Command
1616
public class AddTestMethodExpectedErrorCommand : CommandBase
1717
{
1818
private readonly VBE _vbe;
19-
private readonly NewTestMethodCommand _command;
2019
private readonly RubberduckParserState _state;
2120

22-
public AddTestMethodExpectedErrorCommand(VBE vbe, RubberduckParserState state, NewTestMethodCommand command) : base(LogManager.GetCurrentClassLogger())
21+
public AddTestMethodExpectedErrorCommand(VBE vbe, RubberduckParserState state) : base(LogManager.GetCurrentClassLogger())
2322
{
2423
_vbe = vbe;
25-
_command = command;
2624
_state = state;
2725
}
2826

27+
public const string NamePlaceholder = "%METHODNAME%";
28+
private const string TestMethodBaseName = "TestMethod";
29+
30+
public static readonly string TestMethodExpectedErrorTemplate = string.Concat(
31+
"'@TestMethod\r\n",
32+
"Public Sub ", NamePlaceholder, "() 'TODO ", RubberduckUI.UnitTest_NewMethod_Rename, "\r\n",
33+
" Const ExpectedError As Long = 0 'TODO ", RubberduckUI.UnitTest_NewMethod_ChangeErrorNo, "\r\n",
34+
" On Error GoTo TestFail\r\n",
35+
" \r\n",
36+
" 'Arrange:\r\n\r\n",
37+
" 'Act:\r\n\r\n",
38+
"Assert:\r\n",
39+
" Assert.Fail \"", RubberduckUI.UnitTest_NewMethod_ErrorNotRaised, ".\"\r\n\r\n",
40+
"TestExit:\r\n",
41+
" Exit Sub\r\n",
42+
"TestFail:\r\n",
43+
" If Err.Number = ExpectedError Then\r\n",
44+
" Resume TestExit\r\n",
45+
" Else\r\n",
46+
" Resume Assert\r\n",
47+
" End If\r\n",
48+
"End Sub\r\n"
49+
);
50+
2951
protected override bool CanExecuteImpl(object parameter)
3052
{
31-
if (_state.Status != ParserState.Ready) { return false; }
53+
if (_state.Status != ParserState.Ready || _vbe.ActiveCodePane == null) { return false; }
3254

3355
var testModules = _state.AllUserDeclarations.Where(d =>
3456
d.DeclarationType == DeclarationType.ProceduralModule &&
@@ -49,7 +71,34 @@ protected override bool CanExecuteImpl(object parameter)
4971

5072
protected override void ExecuteImpl(object parameter)
5173
{
52-
_command.NewExpectedErrorTestMethod();
74+
if (_vbe.ActiveCodePane == null) { return; }
75+
76+
try
77+
{
78+
var declaration = _state.GetTestModules().FirstOrDefault(f =>
79+
f.QualifiedName.QualifiedModuleName.Component.CodeModule == _vbe.ActiveCodePane.CodeModule);
80+
81+
if (declaration != null)
82+
{
83+
var module = _vbe.ActiveCodePane.CodeModule;
84+
var name = GetNextTestMethodName(module.Parent);
85+
var body = TestMethodExpectedErrorTemplate.Replace(NamePlaceholder, name);
86+
module.InsertLines(module.CountOfLines, body);
87+
}
88+
}
89+
catch (COMException)
90+
{
91+
}
92+
93+
_state.OnParseRequested(this, _vbe.SelectedVBComponent);
94+
}
95+
96+
private string GetNextTestMethodName(VBComponent component)
97+
{
98+
var names = component.GetTests(_vbe, _state).Select(test => test.Declaration.IdentifierName);
99+
var index = names.Count(n => n.StartsWith(TestMethodBaseName)) + 1;
100+
101+
return string.Concat(TestMethodBaseName, index);
53102
}
54103
}
55104
}
Lines changed: 121 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,10 @@
1+
using System;
2+
using System.Linq;
13
using System.Runtime.InteropServices;
24
using Microsoft.Vbe.Interop;
35
using NLog;
46
using Rubberduck.Parsing.VBA;
7+
using Rubberduck.Settings;
58
using Rubberduck.UnitTesting;
69
using Rubberduck.VBEditor.Extensions;
710

@@ -14,22 +17,134 @@ namespace Rubberduck.UI.Command
1417
public class AddTestModuleCommand : CommandBase
1518
{
1619
private readonly VBE _vbe;
17-
private readonly NewUnitTestModuleCommand _command;
20+
private readonly RubberduckParserState _state;
21+
private readonly IGeneralConfigService _configLoader;
1822

19-
public AddTestModuleCommand(VBE vbe, RubberduckParserState state, NewUnitTestModuleCommand command) : base(LogManager.GetCurrentClassLogger())
23+
public AddTestModuleCommand(VBE vbe, RubberduckParserState state, IGeneralConfigService configLoader)
24+
: base(LogManager.GetCurrentClassLogger())
2025
{
2126
_vbe = vbe;
22-
_command = command;
27+
_state = state;
28+
_configLoader = configLoader;
2329
}
2430

25-
protected override bool CanExecuteImpl(object parameter)
31+
private const string ModuleLateBinding = "Private Assert As Object\r\n";
32+
private const string ModuleEarlyBinding = "Private Assert As New Rubberduck.{0}AssertClass\r\n";
33+
34+
private const string TestModuleEmptyTemplate = "'@TestModule\r\n{0}\r\n";
35+
36+
private const string ModuleInitLateBinding = "Set Assert = CreateObject(\"Rubberduck.{0}AssertClass\")\r\n";
37+
private readonly string _moduleInit = string.Concat(
38+
"'@ModuleInitialize\r\n"
39+
, "Public Sub ModuleInitialize()\r\n"
40+
, " '", RubberduckUI.UnitTest_NewModule_RunOnce, ".\r\n {0}\r\n"
41+
, "End Sub\r\n\r\n"
42+
, "'@ModuleCleanup\r\n"
43+
, "Public Sub ModuleCleanup()\r\n"
44+
, " '", RubberduckUI.UnitTest_NewModule_RunOnce, ".\r\n"
45+
, "End Sub\r\n\r\n"
46+
);
47+
48+
private readonly string _methodInit = string.Concat(
49+
"'@TestInitialize\r\n"
50+
, "Public Sub TestInitialize()\r\n"
51+
, " '", RubberduckUI.UnitTest_NewModule_RunBeforeTest, ".\r\n"
52+
, "End Sub\r\n\r\n"
53+
, "'@TestCleanup\r\n"
54+
, "Public Sub TestCleanup()\r\n"
55+
, " '", RubberduckUI.UnitTest_NewModule_RunAfterTest, ".\r\n"
56+
, "End Sub\r\n\r\n"
57+
);
58+
59+
private const string TestModuleBaseName = "TestModule";
60+
61+
private string GetTestModule(UnitTestSettings settings)
2662
{
27-
return _vbe.HostSupportsUnitTests();
63+
var assertClass = settings.AssertMode == AssertMode.StrictAssert ? string.Empty : "Permissive";
64+
var moduleBinding = settings.BindingMode == BindingMode.EarlyBinding
65+
? string.Format(ModuleEarlyBinding, assertClass)
66+
: ModuleLateBinding;
67+
68+
var formattedModuleTemplate = string.Format(TestModuleEmptyTemplate, moduleBinding);
69+
70+
if (settings.ModuleInit)
71+
{
72+
var lateBindingString = string.Format(ModuleInitLateBinding,
73+
settings.AssertMode == AssertMode.StrictAssert ? string.Empty : "Permissive");
74+
75+
formattedModuleTemplate += string.Format(_moduleInit, settings.BindingMode == BindingMode.EarlyBinding ? string.Empty : lateBindingString);
76+
}
77+
78+
if (settings.MethodInit)
79+
{
80+
formattedModuleTemplate += _methodInit;
81+
}
82+
83+
return formattedModuleTemplate;
2884
}
2985

86+
private VBProject GetProject()
87+
{
88+
return _vbe.ActiveVBProject ?? (_vbe.VBProjects.Count == 1 ? _vbe.VBProjects.Item(1) : null);
89+
}
90+
91+
protected override bool CanExecuteImpl(object parameter)
92+
{
93+
return GetProject() != null &&
94+
_vbe.HostSupportsUnitTests();
95+
}
96+
3097
protected override void ExecuteImpl(object parameter)
3198
{
32-
_command.NewUnitTestModule(_vbe.ActiveVBProject);
99+
var project = parameter as VBProject ?? GetProject();
100+
if (project == null) { return; }
101+
102+
var settings = _configLoader.LoadConfiguration().UserSettings.UnitTestSettings;
103+
VBComponent component;
104+
105+
try
106+
{
107+
if (settings.BindingMode == BindingMode.EarlyBinding)
108+
{
109+
project.EnsureReferenceToAddInLibrary();
110+
}
111+
112+
component = project.VBComponents.Add(vbext_ComponentType.vbext_ct_StdModule);
113+
component.Name = GetNextTestModuleName(project);
114+
115+
var hasOptionExplicit = false;
116+
if (component.CodeModule.CountOfLines > 0 && component.CodeModule.CountOfDeclarationLines > 0)
117+
{
118+
hasOptionExplicit = component.CodeModule.Lines[1, component.CodeModule.CountOfDeclarationLines].Contains("Option Explicit");
119+
}
120+
121+
var options = string.Concat(hasOptionExplicit ? string.Empty : "Option Explicit\r\n", "Option Private Module\r\n\r\n");
122+
123+
var defaultTestMethod = string.Empty;
124+
if (settings.DefaultTestStubInNewModule)
125+
{
126+
defaultTestMethod = AddTestMethodCommand.TestMethodTemplate.Replace(
127+
AddTestMethodCommand.NamePlaceholder, "TestMethod1");
128+
}
129+
130+
component.CodeModule.AddFromString(options + GetTestModule(settings) + defaultTestMethod);
131+
component.Activate();
132+
}
133+
catch (Exception)
134+
{
135+
//can we please comment when we swallow every possible exception?
136+
return;
137+
}
138+
139+
_state.OnParseRequested(this, component);
140+
}
141+
142+
private string GetNextTestModuleName(VBProject project)
143+
{
144+
var names = project.ComponentNames();
145+
var index = names.Count(n => n.StartsWith(TestModuleBaseName)) + 1;
146+
147+
return string.Concat(TestModuleBaseName, index);
33148
}
34149
}
35150
}

0 commit comments

Comments
 (0)