Skip to content

Commit d3fb34f

Browse files
Hosch250retailcoder
authored andcommitted
Make the resolver run immediately after the parse, rather than waitin… (#1641)
* Make the resolver run immediately after the parse, rather than waiting its turn in the StateChanged handler queue * Remove unused method.
1 parent eb8a10d commit d3fb34f

File tree

1 file changed

+29
-31
lines changed

1 file changed

+29
-31
lines changed

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 29 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,6 @@
99
using Antlr4.Runtime.Tree;
1010
using Rubberduck.Parsing.Symbols;
1111
using Rubberduck.VBEditor;
12-
using System.Globalization;
1312
using Rubberduck.Parsing.Preprocessing;
1413
using System.Diagnostics;
1514
using Rubberduck.Parsing.Annotations;
@@ -23,13 +22,7 @@ namespace Rubberduck.Parsing.VBA
2322
{
2423
public class RubberduckParser : IRubberduckParser, IDisposable
2524
{
26-
public RubberduckParserState State
27-
{
28-
get
29-
{
30-
return _state;
31-
}
32-
}
25+
public RubberduckParserState State { get { return _state; } }
3326

3427
private CancellationTokenSource _central = new CancellationTokenSource();
3528
private CancellationTokenSource _resolverTokenSource; // linked to _central later
@@ -46,7 +39,7 @@ private readonly IDictionary<VBComponent, IDictionary<Tuple<string, DeclarationT
4639
private readonly RubberduckParserState _state;
4740
private readonly IAttributeParser _attributeParser;
4841
private readonly Func<IVBAPreprocessor> _preprocessorFactory;
49-
private static readonly Logger _logger = LogManager.GetCurrentClassLogger();
42+
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
5043

5144
public RubberduckParser(
5245
VBE vbe,
@@ -68,13 +61,13 @@ public RubberduckParser(
6861

6962
private void StateOnStateChanged(object sender, EventArgs e)
7063
{
71-
_logger.Debug("RubberduckParser handles OnStateChanged ({0})", _state.Status);
64+
Logger.Debug("RubberduckParser handles OnStateChanged ({0})", _state.Status);
7265

73-
if (_state.Status == ParserState.Parsed)
66+
/*if (_state.Status == ParserState.Parsed)
7467
{
7568
_logger.Debug("(handling OnStateChanged) Starting resolver task");
7669
Resolve(_central.Token); // Tests expect this to be synchronous
77-
}
70+
}*/
7871
}
7972

8073
private void ReparseRequested(object sender, ParseRequestEventArgs e)
@@ -87,7 +80,10 @@ private void ReparseRequested(object sender, ParseRequestEventArgs e)
8780
else
8881
{
8982
Cancel(e.Component);
90-
ParseAsync(e.Component, CancellationToken.None);
83+
ParseAsync(e.Component, CancellationToken.None).Wait();
84+
85+
Logger.Trace("Starting resolver task");
86+
Resolve(_central.Token); // Tests expect this to be synchronous
9187
}
9288
}
9389

@@ -117,11 +113,17 @@ public void Parse()
117113
_componentAttributes.Remove(invalidated);
118114
}
119115

120-
foreach (var vbComponent in components)
116+
/*foreach (var vbComponent in components)
121117
{
122118
_state.ClearStateCache(vbComponent);
123119
ParseComponent(vbComponent);
124-
}
120+
}*/
121+
122+
var parseTasks = components.Select(vbComponent => ParseAsync(vbComponent, CancellationToken.None)).ToArray();
123+
Task.WaitAll(parseTasks);
124+
125+
Logger.Trace("Starting resolver task");
126+
Resolve(_central.Token); // Tests expect this to be synchronous
125127
}
126128

127129
/// <summary>
@@ -174,10 +176,11 @@ private void ParseAll()
174176
_componentAttributes.Remove(invalidated);
175177
}
176178

177-
foreach (var vbComponent in toParse)
178-
{
179-
ParseAsync(vbComponent, CancellationToken.None);
180-
}
179+
var parseTasks = toParse.Select(vbComponent => ParseAsync(vbComponent, CancellationToken.None)).ToArray();
180+
Task.WaitAll(parseTasks);
181+
182+
Logger.Trace("Starting resolver task");
183+
Resolve(_central.Token); // Tests expect this to be synchronous
181184
}
182185

183186
private void AddBuiltInDeclarations(IReadOnlyList<VBProject> projects)
@@ -467,11 +470,6 @@ private void ParseAsyncInternal(VBComponent component, CancellationToken token,
467470
parser.Start(token);
468471
}
469472

470-
private void ParseComponent(VBComponent component, TokenStreamRewriter rewriter = null)
471-
{
472-
ParseAsync(component, CancellationToken.None, rewriter).Wait();
473-
}
474-
475473
private void Resolve(CancellationToken token)
476474
{
477475
var sharedTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_resolverTokenSource.Token, token);
@@ -494,7 +492,7 @@ private void ResolveInternal(CancellationToken token)
494492
foreach (var kvp in _state.ParseTrees)
495493
{
496494
var qualifiedName = kvp.Key;
497-
_logger.Debug("Module '{0}' {1}", qualifiedName.ComponentName, _state.IsNewOrModified(qualifiedName) ? "was modified" : "was NOT modified");
495+
Logger.Debug("Module '{0}' {1}", qualifiedName.ComponentName, _state.IsNewOrModified(qualifiedName) ? "was modified" : "was NOT modified");
498496
// modified module; walk parse tree and re-acquire all declarations
499497
if (token.IsCancellationRequested) return;
500498
ResolveDeclarations(qualifiedName.Component, kvp.Value);
@@ -538,7 +536,7 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
538536
_state.AddDeclaration(projectDeclaration);
539537
}
540538
}
541-
_logger.Debug("Creating declarations for module {0}.", qualifiedModuleName.Name);
539+
Logger.Debug("Creating declarations for module {0}.", qualifiedModuleName.Name);
542540
var declarationsListener = new DeclarationSymbolsListener(qualifiedModuleName, component.Type, _state.GetModuleComments(component), _state.GetModuleAnnotations(component), _state.GetModuleAttributes(component), _projectReferences, projectDeclaration);
543541
ParseTreeWalker.Default.Walk(declarationsListener, tree);
544542
foreach (var createdDeclaration in declarationsListener.CreatedDeclarations)
@@ -548,7 +546,7 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
548546
}
549547
catch (Exception exception)
550548
{
551-
_logger.Error(exception, "Exception thrown acquiring declarations for '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
549+
Logger.Error(exception, "Exception thrown acquiring declarations for '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
552550
lock (_state)
553551
{
554552
_state.SetModuleState(component, ParserState.ResolverError);
@@ -578,7 +576,7 @@ private void ResolveReferences(DeclarationFinder finder, VBComponent component,
578576
return;
579577
}
580578
var qualifiedName = new QualifiedModuleName(component);
581-
_logger.Debug("Resolving identifier references in '{0}'... (thread {1})", qualifiedName.Name, Thread.CurrentThread.ManagedThreadId);
579+
Logger.Debug("Resolving identifier references in '{0}'... (thread {1})", qualifiedName.Name, Thread.CurrentThread.ManagedThreadId);
582580
var resolver = new IdentifierReferenceResolver(qualifiedName, finder);
583581
var listener = new IdentifierReferenceListener(resolver);
584582
if (!string.IsNullOrWhiteSpace(tree.GetText().Trim()))
@@ -589,19 +587,19 @@ private void ResolveReferences(DeclarationFinder finder, VBComponent component,
589587
Stopwatch watch = Stopwatch.StartNew();
590588
walker.Walk(listener, tree);
591589
watch.Stop();
592-
_logger.Debug("Binding Resolution done for component '{0}' in {1}ms (thread {2})", component.Name, watch.ElapsedMilliseconds, Thread.CurrentThread.ManagedThreadId);
590+
Logger.Debug("Binding Resolution done for component '{0}' in {1}ms (thread {2})", component.Name, watch.ElapsedMilliseconds, Thread.CurrentThread.ManagedThreadId);
593591
_state.RebuildSelectionCache();
594592
state = ParserState.Ready;
595593
}
596594
catch (Exception exception)
597595
{
598-
_logger.Error(exception, "Exception thrown resolving '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
596+
Logger.Error(exception, "Exception thrown resolving '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
599597
state = ParserState.ResolverError;
600598
}
601599
}
602600

603601
_state.SetModuleState(component, state);
604-
_logger.Debug("'{0}' is {1} (thread {2})", component.Name, _state.GetModuleState(component), Thread.CurrentThread.ManagedThreadId);
602+
Logger.Debug("'{0}' is {1} (thread {2})", component.Name, _state.GetModuleState(component), Thread.CurrentThread.ManagedThreadId);
605603
}
606604

607605
public void Dispose()

0 commit comments

Comments
 (0)