Skip to content

Commit

Permalink
Initial version of Busy state and SuspendParser function
Browse files Browse the repository at this point in the history
  • Loading branch information
bclothier committed Apr 23, 2018
1 parent 14743dc commit f9469e9
Show file tree
Hide file tree
Showing 5 changed files with 103 additions and 48 deletions.
9 changes: 9 additions & 0 deletions Rubberduck.Core/UI/RubberduckUI.Designer.cs

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

3 changes: 3 additions & 0 deletions Rubberduck.Core/UI/RubberduckUI.resx
Expand Up @@ -1827,4 +1827,7 @@ NOTE: Restart is required for the setting to take effect.</value>
<data name="InspectionSettings_FilterDescription" xml:space="preserve">
<value>Filter by Description:</value>
</data>
<data name="ParserState_Busy" xml:space="preserve">
<value>Busy</value>
</data>
</root>
107 changes: 59 additions & 48 deletions Rubberduck.Core/UnitTesting/TestEngine.cs
Expand Up @@ -38,7 +38,7 @@ public TestEngine(TestExplorerModel model, IVBE vbe, RubberduckParserState state
_fakesFactory = fakesFactory;
_typeLibApi = typeLibApi;
_uiDispatcher = uiDispatcher;

_state.StateChanged += StateChangedHandler;
}

Expand Down Expand Up @@ -89,66 +89,77 @@ public void Run(IEnumerable<TestMethod> tests)

private void RunInternal(IEnumerable<TestMethod> tests)
{
var testMethods = tests as IList<TestMethod> ?? tests.ToList();
if (!testMethods.Any())
if (_state.Status != ParserState.Ready)
{
return;
}

var modules = testMethods.GroupBy(test => test.Declaration.QualifiedName.QualifiedModuleName);
foreach (var module in modules)
_state.SuspendParser(this, () =>
{
var testInitialize = module.Key.FindTestInitializeMethods(_state).ToList();
var testCleanup = module.Key.FindTestCleanupMethods(_state).ToList();

var capturedModule = module;
var moduleTestMethods = testMethods
.Where(test => test.Declaration.QualifiedName.QualifiedModuleName.ProjectId == capturedModule.Key.ProjectId
&& test.Declaration.QualifiedName.QualifiedModuleName.ComponentName == capturedModule.Key.ComponentName);
var testMethods = tests as IList<TestMethod> ?? tests.ToList();
if (!testMethods.Any())
{
return;
}
var fakes = _fakesFactory.Create();
Run(module.Key.FindModuleInitializeMethods(_state));
foreach (var test in moduleTestMethods)
var modules = testMethods.GroupBy(test => test.Declaration.QualifiedName.QualifiedModuleName);
foreach (var module in modules)
{
// no need to run setup/teardown for ignored tests
if (test.Declaration.Annotations.Any(a => a.AnnotationType == AnnotationType.IgnoreTest))
var testInitialize = module.Key.FindTestInitializeMethods(_state).ToList();
var testCleanup = module.Key.FindTestCleanupMethods(_state).ToList();
var capturedModule = module;
var moduleTestMethods = testMethods
.Where(test =>
test.Declaration.QualifiedName.QualifiedModuleName.ProjectId == capturedModule.Key.ProjectId
&& test.Declaration.QualifiedName.QualifiedModuleName.ComponentName ==
capturedModule.Key.ComponentName);
var fakes = _fakesFactory.Create();
RunInternal(module.Key.FindModuleInitializeMethods(_state));
foreach (var test in moduleTestMethods)
{
test.UpdateResult(TestOutcome.Ignored);
OnTestCompleted();
continue;
}
// no need to run setup/teardown for ignored tests
if (test.Declaration.Annotations.Any(a => a.AnnotationType == AnnotationType.IgnoreTest))
{
test.UpdateResult(TestOutcome.Ignored);
OnTestCompleted();
continue;
}
var stopwatch = new Stopwatch();
stopwatch.Start();
try
{
fakes.StartTest();
RunInternal(testInitialize);
test.Run();
RunInternal(testCleanup);
}
catch (COMException ex)
{
Logger.Error(ex, "Unexpected COM exception while running tests.",
test.Declaration?.QualifiedName);
test.UpdateResult(TestOutcome.Inconclusive, RubberduckUI.Assert_ComException);
}
finally
{
fakes.StopTest();
}
stopwatch.Stop();
test.Result.SetDuration(stopwatch.ElapsedMilliseconds);
var stopwatch = new Stopwatch();
stopwatch.Start();

try
{
fakes.StartTest();
Run(testInitialize);
test.Run();
Run(testCleanup);
}
catch (COMException ex)
{
Logger.Error(ex, "Unexpected COM exception while running tests.", test.Declaration?.QualifiedName);
test.UpdateResult(TestOutcome.Inconclusive, RubberduckUI.Assert_ComException);
}
finally
{
fakes.StopTest();
OnTestCompleted();
Model.AddExecutedTest(test);
}

stopwatch.Stop();
test.Result.SetDuration(stopwatch.ElapsedMilliseconds);

OnTestCompleted();
Model.AddExecutedTest(test);
RunInternal(module.Key.FindModuleCleanupMethods(_state));
}
Run(module.Key.FindModuleCleanupMethods(_state));
}
});
}

private void Run(IEnumerable<Declaration> members)
private void RunInternal(IEnumerable<Declaration> members)
{
var groupedMembers = members.GroupBy(m => m.ProjectName);
foreach (var group in groupedMembers)
Expand Down
4 changes: 4 additions & 0 deletions Rubberduck.Parsing/VBA/ParserState.cs
Expand Up @@ -40,6 +40,10 @@ public enum ParserState
/// </summary>
Ready,
/// <summary>
/// The parser cannot run during that time (e.g. unit tests are running); any parse requests will be queued.
/// </summary>
Busy,
/// <summary>
/// Parsing could not be completed for one or more modules.
/// </summary>
Error,
Expand Down
28 changes: 28 additions & 0 deletions Rubberduck.Parsing/VBA/RubberduckParserState.cs
Expand Up @@ -911,6 +911,12 @@ public bool RemoveDeclaration(Declaration declaration)
/// <param name="requestor">The object requesting a reparse.</param>
public void OnParseRequested(object requestor)
{
if (Status == ParserState.Busy)
{
_queuedRequestors.Add(requestor);
return;
}

var handler = ParseRequest;
if (handler != null && IsEnabled)
{
Expand Down Expand Up @@ -978,6 +984,28 @@ public void AddAttributesRewriter(QualifiedModuleName module, IModuleRewriter at
_moduleStates[key].SetAttributesRewriter(attributesRewriter);
}

private List<object> _queuedRequestors => new List<object>();
public void SuspendParser(object requestor, Action busyAction)
{
if (Status != ParserState.Ready)
{
throw new InvalidOperationException("Cannot suspend the parser while it is running. Either cancel or wait for Ready status");
}

SetStatusAndFireStateChanged(requestor, ParserState.Busy, CancellationToken.None);
busyAction.Invoke();
if (_queuedRequestors.Any())
{
var lastRequestor = _queuedRequestors.Last();
_queuedRequestors.Clear();
OnParseRequested(lastRequestor);;
}
else
{
SetStatusAndFireStateChanged(requestor, ParserState.Ready, CancellationToken.None);
}
}

private bool _isDisposed;
public void Dispose()
{
Expand Down

0 comments on commit f9469e9

Please sign in to comment.