Skip to content

Commit

Permalink
Remove test scope flag and create a testing subtype for ParseCoordina…
Browse files Browse the repository at this point in the history
…tor (TestParseCoordinator class)
  • Loading branch information
bclothier committed Jun 23, 2018
1 parent a75e056 commit efe57a5
Show file tree
Hide file tree
Showing 2 changed files with 37 additions and 21 deletions.
31 changes: 14 additions & 17 deletions Rubberduck.Parsing/VBA/ParseCoordinator.cs
Expand Up @@ -12,6 +12,10 @@

namespace Rubberduck.Parsing.VBA
{
/// <remarks>
/// Note that for unit tests, TestParseCoodrinator is used in its place
/// to support synchronous parse from BeginParse.
/// </remarks>
public class ParseCoordinator : IParseCoordinator
{
public RubberduckParserState State { get; }
Expand All @@ -25,15 +29,12 @@ public class ParseCoordinator : IParseCoordinator
private readonly ConcurrentStack<object> _requestorStack;
private bool _isSuspended;

private readonly bool _isTestScope;

public ParseCoordinator(
RubberduckParserState state,
IParsingStageService parsingStageService,
IParsingCacheService parsingCacheService,
IProjectManager projectManager,
IParserStateManager parserStateManager,
bool isTestScope = false)
IParserStateManager parserStateManager)
{
if (state == null)
{
Expand Down Expand Up @@ -61,7 +62,6 @@ public class ParseCoordinator : IParseCoordinator
_projectManager = projectManager;
_parsingCacheService = parsingCacheService;
_parserStateManager = parserStateManager;
_isTestScope = isTestScope;

state.ParseRequest += ReparseRequested;
state.SuspendRequest += SuspendRequested;
Expand Down Expand Up @@ -174,16 +174,13 @@ public void SuspendRequested(object sender, RubberduckStatusSuspendParserEventAr
}
}

private void BeginParse(object sender, CancellationToken token)
/// <remarks>
/// Overriden in the unit test project to facilicate synchronous unit tests
/// Refer to TestParserCoordinator class in the unit test project.
/// </remarks>
protected virtual void BeginParse(object sender, CancellationToken token)
{
if (!_isTestScope)
{
Task.Run(() => ParseAll(sender, token), token);
}
else
{
ParseInternal(token);
}
Task.Run(() => ParseAll(sender, token), token);
}

private void Cancel(bool createNewTokenSource = true)
Expand All @@ -205,7 +202,7 @@ private void Cancel(bool createNewTokenSource = true)
}

/// <summary>
/// For the use of tests only
/// For the use of tests & reflection API only
/// </summary>
public void Parse(CancellationTokenSource token)
{
Expand All @@ -214,7 +211,7 @@ public void Parse(CancellationTokenSource token)
}

/// <summary>
/// For the use of tests only
/// For the use of tests & reflection API only
/// </summary>
private void SetSavedCancellationTokenSource(CancellationTokenSource tokenSource)
{
Expand All @@ -225,7 +222,7 @@ private void SetSavedCancellationTokenSource(CancellationTokenSource tokenSource
oldTokenSource?.Dispose();
}

private void ParseInternal(CancellationToken token)
protected void ParseInternal(CancellationToken token)
{
var lockTaken = false;
try
Expand Down
27 changes: 23 additions & 4 deletions RubberduckTests/Mocks/MockParser.cs
Expand Up @@ -15,11 +15,31 @@
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.PreProcessing;
using Rubberduck.VBEditor.ComManagement;
using Rubberduck.VBEditor.Events;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;

namespace RubberduckTests.Mocks
{
internal class TestParseCoordinator : ParseCoordinator
{
public TestParseCoordinator(
RubberduckParserState state,
IParsingStageService parsingStageService,
IParsingCacheService parsingCacheService,
IProjectManager projectManager,
IParserStateManager parserStateManager) : base(
state,
parsingStageService,
parsingCacheService,
projectManager,
parserStateManager)
{ }

protected override void BeginParse(object sender, CancellationToken token)
{
ParseInternal(token);
}
}

public static class MockParser
{
public static RubberduckParserState ParseString(string inputCode, out QualifiedModuleName qualifiedModuleName)
Expand Down Expand Up @@ -105,13 +125,12 @@ public static ParseCoordinator Create(IVBE vbe, RubberduckParserState state, IAt
supertypeClearer
);

return new ParseCoordinator(
return new TestParseCoordinator(
state,
parsingStageService,
parsingCacheService,
projectManager,
parserStateManager,
true);
parserStateManager);
}

public static RubberduckParserState CreateAndParse(IVBE vbe, IInspectionListener listener, IEnumerable<string> testLibraries = null)
Expand Down

0 comments on commit efe57a5

Please sign in to comment.