Skip to content

Commit 94197a9

Browse files
committed
Introduce high priority state changed event
The order in which event handlers are executed is not guaranteed. Because of this we had the problem that the status message change for the state change to Ready happened after the status message change in the inspections, which are executed async. As the result, the message 'Inspection' was immediately overwritten and did not last until the inspections had finished.
1 parent 286b55c commit 94197a9

File tree

2 files changed

+36
-15
lines changed

2 files changed

+36
-15
lines changed

Rubberduck.Core/UI/Command/MenuItems/CommandBars/RubberduckCommandBar.cs

Lines changed: 14 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
using System.Linq;
55
using System.Runtime.InteropServices;
66
using Rubberduck.Resources;
7-
using Rubberduck.Parsing;
87
using Rubberduck.Parsing.Symbols;
98
using Rubberduck.Parsing.UIContext;
109
using Rubberduck.Parsing.VBA;
@@ -15,18 +14,18 @@ namespace Rubberduck.UI.Command.MenuItems.CommandBars
1514
public class RubberduckCommandBar : AppCommandBarBase, IDisposable
1615
{
1716
private readonly IContextFormatter _formatter;
18-
private readonly IParseCoordinator _parser;
17+
private readonly RubberduckParserState _state;
1918
private readonly ISelectionChangeService _selectionService;
2019

21-
public RubberduckCommandBar(IParseCoordinator parser, IEnumerable<ICommandMenuItem> items, IContextFormatter formatter, ISelectionChangeService selectionService, IUiDispatcher uiDispatcher)
20+
public RubberduckCommandBar(RubberduckParserState state, IEnumerable<ICommandMenuItem> items, IContextFormatter formatter, ISelectionChangeService selectionService, IUiDispatcher uiDispatcher)
2221
: base("Rubberduck", CommandBarPosition.Top, items, uiDispatcher)
2322
{
24-
_parser = parser;
23+
_state = state;
2524
_formatter = formatter;
2625
_selectionService = selectionService;
2726

28-
_parser.State.StateChanged += OnParserStateChanged;
29-
_parser.State.StatusMessageUpdate += OnParserStatusMessageUpdate;
27+
_state.StateChangedHighPriority += OnParserStateChanged;
28+
_state.StatusMessageUpdate += OnParserStatusMessageUpdate;
3029
_selectionService.SelectionChanged += OnSelectionChange;
3130
}
3231

@@ -36,14 +35,14 @@ public override void Initialize()
3635
{
3736
base.Initialize();
3837
SetStatusLabelCaption(ParserState.Pending);
39-
EvaluateCanExecute(_parser.State);
38+
EvaluateCanExecute(_state);
4039
}
4140

4241
private Declaration _lastDeclaration;
4342
private ParserState _lastStatus = ParserState.None;
4443
private void EvaluateCanExecute(RubberduckParserState state, Declaration selected)
4544
{
46-
var currentStatus = _parser.State.Status;
45+
var currentStatus = _state.Status;
4746
if (_lastStatus == currentStatus &&
4847
(selected == null || selected.Equals(_lastDeclaration)) &&
4948
(selected != null || _lastDeclaration == null))
@@ -69,7 +68,7 @@ private void OnSelectionChange(object sender, DeclarationChangedEventArgs e)
6968
var description = e.Declaration?.DescriptionString ?? string.Empty;
7069
//& renders the next character as if it was an accelerator.
7170
SetContextSelectionCaption(caption?.Replace("&", "&&"), refCount, description);
72-
EvaluateCanExecute(_parser.State, e.Declaration);
71+
EvaluateCanExecute(_state, e.Declaration);
7372
}
7473

7574

@@ -82,14 +81,14 @@ private void OnParserStatusMessageUpdate(object sender, RubberduckStatusMessageE
8281
message = RubberduckUI.ParserState_LoadingReference;
8382
}
8483

85-
SetStatusLabelCaption(message, _parser.State.ModuleExceptions.Count);
84+
SetStatusLabelCaption(message, _state.ModuleExceptions.Count);
8685
}
8786

8887
private void OnParserStateChanged(object sender, EventArgs e)
8988
{
90-
_lastStatus = _parser.State.Status;
91-
EvaluateCanExecute(_parser.State);
92-
SetStatusLabelCaption(_parser.State.Status, _parser.State.ModuleExceptions.Count);
89+
_lastStatus = _state.Status;
90+
EvaluateCanExecute(_state);
91+
SetStatusLabelCaption(_state.Status, _state.ModuleExceptions.Count);
9392
}
9493

9594
public void SetStatusLabelCaption(ParserState state, int? errorCount = null)
@@ -182,8 +181,8 @@ protected virtual void Dispose(bool disposing)
182181
}
183182

184183
_selectionService.SelectionChanged -= OnSelectionChange;
185-
_parser.State.StateChanged -= OnParserStateChanged;
186-
_parser.State.StatusMessageUpdate -= OnParserStatusMessageUpdate;
184+
_state.StateChanged -= OnParserStateChanged;
185+
_state.StatusMessageUpdate -= OnParserStatusMessageUpdate;
187186

188187
RemoveCommandBar();
189188

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -359,6 +359,7 @@ public IReadOnlyList<Tuple<QualifiedModuleName, SyntaxErrorException>> ModuleExc
359359
}
360360
}
361361

362+
public event EventHandler<ParserStateEventArgs> StateChangedHighPriority;
362363
public event EventHandler<ParserStateEventArgs> StateChanged;
363364

364365
private int _stateChangedInvocations;
@@ -367,6 +368,27 @@ private void OnStateChanged(object requestor, CancellationToken token, ParserSta
367368
Interlocked.Increment(ref _stateChangedInvocations);
368369

369370
Logger.Info($"{nameof(RubberduckParserState)} ({_stateChangedInvocations}) is invoking {nameof(StateChanged)} ({Status})");
371+
372+
var highPriorityHandler = StateChangedHighPriority;
373+
if (highPriorityHandler != null && !token.IsCancellationRequested)
374+
{
375+
try
376+
{
377+
var args = new ParserStateEventArgs(state, oldStatus, token);
378+
highPriorityHandler.Invoke(requestor, args);
379+
}
380+
catch (OperationCanceledException cancellation)
381+
{
382+
throw;
383+
}
384+
catch (Exception e)
385+
{
386+
// Error state, because this implies consumers are not exception-safe!
387+
// this behaviour could leave us in a state where some consumers have correctly updated and some have not
388+
Logger.Error(e, "An exception occurred when notifying consumers of updated parser state.");
389+
}
390+
}
391+
370392
var handler = StateChanged;
371393
if (handler != null && !token.IsCancellationRequested)
372394
{

0 commit comments

Comments
 (0)