Skip to content

Commit

Permalink
Add a separate lock for managing the suspension marker & stack, separ…
Browse files Browse the repository at this point in the history
…ate from the lock for managing the state.

Update the unit tests.
Add a timeout
Add debug assertion for unwanted suspension requests while inside another suspension request.
  • Loading branch information
bclothier committed Jun 20, 2018
1 parent 59d3a2f commit 266ae63
Show file tree
Hide file tree
Showing 3 changed files with 111 additions and 50 deletions.
100 changes: 57 additions & 43 deletions Rubberduck.Parsing/VBA/ParseCoordinator.cs
Expand Up @@ -23,7 +23,7 @@ public class ParseCoordinator : IParseCoordinator
private readonly IParsingCacheService _parsingCacheService;
private readonly IParserStateManager _parserStateManager;
private readonly ConcurrentStack<object> _requestorStack;
private long _suspensionIteration;
private bool _isSuspended;

private readonly bool _isTestScope;

Expand Down Expand Up @@ -75,37 +75,22 @@ public class ParseCoordinator : IParseCoordinator

private readonly object _cancellationSyncObject = new object();
private readonly object _parsingRunSyncObject = new object();
private readonly object _suspendStackSyncObject = new object();
private readonly ReaderWriterLockSlim _parsingSuspendLock = new ReaderWriterLockSlim(LockRecursionPolicy.NoRecursion);

private void ReparseRequested(object sender, EventArgs e)
{
CancellationToken token;
lock (_cancellationSyncObject)
{
try
lock (_suspendStackSyncObject)
{
// Removes the need for recursion policy. In unlikely event where the
// same thread that is executing the busyAction of the suspendRequest
// has requested a reparse, we can skip taking a read lock, since we already
// have the write lock further up the thread's call stack.
if (!_parsingSuspendLock.IsWriteLockHeld)
{
_parsingSuspendLock.EnterReadLock();
}
var isSuspended = Interlocked.Read(ref _suspensionIteration);
if (isSuspended != 0)
if (_isSuspended)
{
_requestorStack.Push(sender);
return;
}
}
finally
{
if (_parsingSuspendLock.IsReadLockHeld)
{
_parsingSuspendLock.ExitReadLock();
}
}

Cancel();

Expand All @@ -124,46 +109,48 @@ private void ReparseRequested(object sender, EventArgs e)
public void SuspendRequested(object sender, RubberduckStatusSuspendParserEventArgs e)
{
object parseRequestor = null;
ParserState originalStatus;

try
{
if (_parsingSuspendLock.IsReadLockHeld)
{
Logger.Warn("A suspension action was attempted while a read lock was held.");
e.Declined = true;
const string errorMessage =
"A suspension action was attempted while a read lock was held. This indicates a bug in the code logic as suspension should not be requested from same thread that has a read lock.";
Logger.Error(errorMessage);
#if DEBUG
Debug.Assert(false, errorMessage);
#endif
return;
}
_parsingSuspendLock.EnterWriteLock();
Interlocked.Add(ref _suspensionIteration, 1);
var originalStatus = State.Status;
Cancel();
if (!_parsingSuspendLock.TryEnterWriteLock(e.MillisecondsTimeout))
{
e.TimedOut = true;
return;
}

lock (_suspendStackSyncObject)
{
_isSuspended = true;
}

originalStatus = State.Status;
_parserStateManager.SetStatusAndFireStateChanged(e.Requestor, ParserState.Busy,
CancellationToken.None);
e.BusyAction.Invoke();
if (_requestorStack.TryPop(out var lastRequestor))
{
_requestorStack.Clear();
parseRequestor = lastRequestor;
}
else

lock (_suspendStackSyncObject)
{
if (originalStatus != ParserState.Ready)
{
// We can't assume that we can return to any other state that's not "Ready"; it's better
// to request a state evaluation
_parserStateManager.EvaluateOverallParserState(CancellationToken.None);
}
else
_isSuspended = false;
if (_requestorStack.TryPop(out var lastRequestor))
{
_parserStateManager.SetStatusAndFireStateChanged(e.Requestor, originalStatus,
CancellationToken.None);
_requestorStack.Clear();
parseRequestor = lastRequestor;
}
}
_requestorStack.Clear();
}
finally
{
Interlocked.Exchange(ref _suspensionIteration, 0);
if (_parsingSuspendLock.IsWriteLockHeld)
{
_parsingSuspendLock.ExitWriteLock();
Expand All @@ -175,6 +162,17 @@ public void SuspendRequested(object sender, RubberduckStatusSuspendParserEventAr
Cancel();
BeginParse(parseRequestor, _currentCancellationTokenSource.Token);
}
else if (originalStatus != ParserState.Ready)
{
// We can't assume that we can return to any other state that's not "Ready"; it's better
// to request a state evaluation
_parserStateManager.EvaluateOverallParserState(CancellationToken.None);
}
else
{
_parserStateManager.SetStatusAndFireStateChanged(e.Requestor, originalStatus,
CancellationToken.None);
}
}

private void BeginParse(object sender, CancellationToken token)
Expand Down Expand Up @@ -234,6 +232,10 @@ private void ParseInternal(CancellationToken token)
try
{
Monitor.Enter(_parsingRunSyncObject, ref lockTaken);
if (!_parsingSuspendLock.IsWriteLockHeld)
{
_parsingSuspendLock.EnterReadLock();
}
ParseAllInternal(this, token);
}
catch (OperationCanceledException)
Expand All @@ -242,6 +244,10 @@ private void ParseInternal(CancellationToken token)
}
finally
{
if (_parsingSuspendLock.IsReadLockHeld)
{
_parsingSuspendLock.ExitReadLock();
}
if (lockTaken)
{
Monitor.Exit(_parsingRunSyncObject);
Expand Down Expand Up @@ -399,7 +405,11 @@ private void ParseAll(object requestor, CancellationToken token)
try
{
Monitor.Enter(_parsingRunSyncObject, ref lockTaken);

if (!_parsingSuspendLock.IsWriteLockHeld)
{
_parsingSuspendLock.EnterReadLock();
}

watch = Stopwatch.StartNew();
Logger.Debug("Parsing run started. (thread {0}).", Thread.CurrentThread.ManagedThreadId);

Expand All @@ -421,6 +431,10 @@ private void ParseAll(object requestor, CancellationToken token)
finally
{
if (watch != null && watch.IsRunning) watch.Stop();
if (_parsingSuspendLock.IsReadLockHeld)
{
_parsingSuspendLock.ExitReadLock();
}
if (lockTaken) Monitor.Exit(_parsingRunSyncObject);
}
if (watch != null) Logger.Debug("Parsing run finished after {0}s. (thread {1}).", watch.Elapsed.TotalSeconds, Thread.CurrentThread.ManagedThreadId);
Expand Down
17 changes: 12 additions & 5 deletions Rubberduck.Parsing/VBA/RubberduckParserState.cs
Expand Up @@ -59,15 +59,17 @@ public ParserStateEventArgs(ParserState state, CancellationToken token)

public class RubberduckStatusSuspendParserEventArgs : EventArgs
{
public RubberduckStatusSuspendParserEventArgs(object requestor, Action busyAction)
public RubberduckStatusSuspendParserEventArgs(object requestor, Action busyAction, int millisecondsTimeout)
{
Requestor = requestor;
BusyAction = busyAction;
MillisecondsTimeout = millisecondsTimeout;
}

public bool Declined { get; set; }
public object Requestor { get; }
public Action BusyAction { get; }
public int MillisecondsTimeout { get; }
public bool TimedOut { get; set; }
}

public class RubberduckStatusMessageEventArgs : EventArgs
Expand Down Expand Up @@ -932,14 +934,19 @@ public void OnParseRequested(object requestor)
}
}

public bool OnSuspendParser(object requestor, Action busyAction)
public bool OnSuspendParser(object requestor, Action busyAction, int millisecondsTimeout = 10000)
{
if (millisecondsTimeout <= 0)
{
throw new ArgumentOutOfRangeException(nameof(millisecondsTimeout));
}

var handler = SuspendRequest;
if (handler != null && IsEnabled)
{
var args = new RubberduckStatusSuspendParserEventArgs(requestor, busyAction);
var args = new RubberduckStatusSuspendParserEventArgs(requestor, busyAction, millisecondsTimeout);
handler.Invoke(requestor, args);
return !args.Declined;
return !args.TimedOut;
}

return false;
Expand Down
44 changes: 42 additions & 2 deletions RubberduckTests/ParserState/ParserStateTests.cs
Expand Up @@ -128,7 +128,6 @@ public void Test_RPS_SuspendParser_Interrupted_IsQueued()
wasBusy = state.Status == ParserState.Busy;
});
});
result.Wait();
wasBusy = false;
}
}
Expand All @@ -149,6 +148,48 @@ public void Test_RPS_SuspendParser_Interrupted_IsQueued()
Assert.AreEqual(1, reparseAfterBusy);
}

[Test]
[Category("ParserState")]
public void Test_RPS_SuspendParser_Interrupted_Deadlock()
{
var vbe = MockVbeBuilder.BuildFromSingleModule("", ComponentType.StandardModule, out var _);
var state = MockParser.CreateAndParse(vbe.Object);

var wasSuspended = false;
var wasSuspensionExecuted = false;

// The cancellation token exists primarily to prevent
// unwanted inlining of the tasks.
// See: https://stackoverflow.com/questions/12245935/is-task-factory-startnew-guaranteed-to-use-another-thread-than-the-calling-thr
var source = new CancellationTokenSource();
Task result2 = null;

state.StateChanged += (o, e) =>
{
if (e.State == ParserState.Started)
{
result2 = Task.Run(() =>
{
wasSuspensionExecuted =
state.OnSuspendParser(this, () => { wasSuspended = state.Status == ParserState.Busy; },
20);
}, source.Token);
result2.Wait(source.Token);
}
};
var result1 = Task.Run(() =>
{
state.OnParseRequested(this);
}, source.Token);
result1.Wait(source.Token);
while (result2 == null)
{
Thread.Sleep(1);
}
result2.Wait();
Assert.IsFalse(wasSuspended, "wasSuspended was set to true");
Assert.IsFalse(wasSuspensionExecuted, "wasSuspensionExecuted was set to true");
}

[Test]
[Category("ParserState")]
Expand All @@ -175,7 +216,6 @@ public void Test_RPS_SuspendParser_Interrupted_TwoRequests_IsQueued()
wasRunning = true;
result2 = Task.Run(() => state.OnParseRequested(this));
});
result1.Wait();
return;
}
}
Expand Down

0 comments on commit 266ae63

Please sign in to comment.