Skip to content

Commit d53c9a6

Browse files
committed
Fix test setup for TestEngine
The tests failed prematurely because the actual work was done on a background thread that had not reached to end when the assert was executed.
1 parent b49f2d5 commit d53c9a6

File tree

2 files changed

+46
-9
lines changed

2 files changed

+46
-9
lines changed

Rubberduck.UnitTesting/UnitTesting/TestEngine.cs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ namespace Rubberduck.UnitTesting
1919
// FIXME litter logging around here
2020
internal class TestEngine : ITestEngine
2121
{
22-
private static readonly ParserState[] AllowedRunStates =
22+
protected static readonly ParserState[] AllowedRunStates =
2323
{
2424
ParserState.Ready
2525
};
@@ -171,7 +171,7 @@ public void RequestCancellation()
171171
CancellationRequested = true;
172172
}
173173

174-
private void RunInternal(IEnumerable<TestMethod> tests)
174+
protected virtual void RunInternal(IEnumerable<TestMethod> tests)
175175
{
176176
if (!CanRun)
177177
{
@@ -199,15 +199,15 @@ private void EnsureRubberduckIsReferencedForEarlyBoundTests()
199199
}
200200
}
201201

202-
private void RunWhileSuspended(IEnumerable<TestMethod> tests)
202+
protected void RunWhileSuspended(IEnumerable<TestMethod> tests)
203203
{
204204
//Running the tests has to be done on the UI thread, so we push the task to it from within suspension of the parser.
205205
//We have to wait for the completion to make sure that the suspension only ends after tests have been completed.
206-
var testTask = _uiDispatcher.StartTask(() => RunWhileSuspendedOnUIThread(tests));
206+
var testTask = _uiDispatcher.StartTask(() => RunWhileSuspendedOnUiThread(tests));
207207
testTask.Wait();
208208
}
209209

210-
private void RunWhileSuspendedOnUIThread(IEnumerable<TestMethod> tests)
210+
private void RunWhileSuspendedOnUiThread(IEnumerable<TestMethod> tests)
211211
{
212212
var testMethods = tests as IList<TestMethod> ?? tests.ToList();
213213
if (!testMethods.Any())

RubberduckTests/UnitTesting/MockedTestEngine.cs

Lines changed: 41 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
using System.Collections.Generic;
33
using System.Diagnostics.CodeAnalysis;
44
using System.Linq;
5+
using System.Threading.Tasks;
56
using Moq;
67
using NUnit.Framework;
78
using Rubberduck.Parsing.UIContext;
@@ -47,8 +48,17 @@ internal class MockedTestEngine : IDisposable
4748

4849
private MockedTestEngine()
4950
{
50-
Dispatcher.Setup(d => d.InvokeAsync(It.IsAny<Action>())).Callback((Action action) => action.Invoke()).Verifiable();
51-
51+
Dispatcher.Setup(d => d.InvokeAsync(It.IsAny<Action>()))
52+
.Callback((Action action) => action.Invoke())
53+
.Verifiable();
54+
Dispatcher.Setup(d => d.StartTask(It.IsAny<Action>(), It.IsAny<TaskCreationOptions>()))
55+
.Returns((Action action, TaskCreationOptions options) =>
56+
{
57+
action.Invoke();
58+
return Task.CompletedTask;
59+
})
60+
.Verifiable();
61+
5262
TypeLib.Setup(tlm => tlm.Dispose()).Verifiable();
5363
WrapperProvider.Setup(p => p.TypeLibWrapperFromProject(It.IsAny<string>())).Returns(TypeLib.Object).Verifiable();
5464

@@ -64,7 +74,7 @@ public MockedTestEngine(string testModuleCode) : this()
6474

6575
Vbe = builder.Build();
6676
ParserState = MockParser.Create(Vbe.Object).State;
67-
TestEngine = new TestEngine(ParserState, _fakesFactory.Object, VbeInteraction.Object, WrapperProvider.Object, Dispatcher.Object, Vbe.Object);
77+
TestEngine = new SynchronouslySuspendingTestEngine(ParserState, _fakesFactory.Object, VbeInteraction.Object, WrapperProvider.Object, Dispatcher.Object, Vbe.Object);
6878
}
6979

7080
public MockedTestEngine(IReadOnlyList<string> moduleNames, IReadOnlyList<int> methodCounts) : this()
@@ -87,7 +97,7 @@ public MockedTestEngine(IReadOnlyList<string> moduleNames, IReadOnlyList<int> me
8797
project.AddProjectToVbeBuilder();
8898
Vbe = builder.Build();
8999
ParserState = MockParser.Create(Vbe.Object).State;
90-
TestEngine = new TestEngine(ParserState, _fakesFactory.Object, VbeInteraction.Object, WrapperProvider.Object, Dispatcher.Object, Vbe.Object);
100+
TestEngine = new SynchronouslySuspendingTestEngine(ParserState, _fakesFactory.Object, VbeInteraction.Object, WrapperProvider.Object, Dispatcher.Object, Vbe.Object);
91101
}
92102

93103
public MockedTestEngine(int testMethodCount)
@@ -246,5 +256,32 @@ Public Sub TestCleanup()
246256
'this method runs after every test in the module.
247257
End Sub
248258
";
259+
260+
private class SynchronouslySuspendingTestEngine : TestEngine
261+
{
262+
private readonly RubberduckParserState _state;
263+
264+
public SynchronouslySuspendingTestEngine(
265+
RubberduckParserState state,
266+
IFakesFactory fakesFactory,
267+
IVBEInteraction declarationRunner,
268+
ITypeLibWrapperProvider wrapperProvider,
269+
IUiDispatcher uiDispatcher,
270+
IVBE vbe)
271+
: base(state, fakesFactory, declarationRunner, wrapperProvider, uiDispatcher, vbe)
272+
{
273+
_state = state;
274+
}
275+
276+
protected override void RunInternal(IEnumerable<TestMethod> tests)
277+
{
278+
if (!CanRun)
279+
{
280+
return;
281+
}
282+
//We have to do this on the same thread here to guarantee that the actions runs before the assert in the unit tests is called.
283+
_state.OnSuspendParser(this, AllowedRunStates, () => RunWhileSuspended(tests));
284+
}
285+
}
249286
}
250287
}

0 commit comments

Comments
 (0)