Skip to content

Commit 1fb5ecc

Browse files
committed
Make parser/resolver run more asynchronously.
1 parent b57986b commit 1fb5ecc

File tree

2 files changed

+120
-79
lines changed

2 files changed

+120
-79
lines changed

Rubberduck.Parsing/VBA/ComponentParseTask.cs

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -75,23 +75,26 @@ public void Start(CancellationToken token)
7575
Tokens = stream,
7676
Attributes = attributes,
7777
Comments = comments,
78-
Annotations = annotationListener.Annotations
78+
Annotations = annotationListener.Annotations,
79+
Component = _component
7980
});
8081
}
8182
catch (COMException exception)
8283
{
8384
_logger.Error(exception, "Exception thrown in thread {0}.", Thread.CurrentThread.ManagedThreadId);
8485
ParseFailure.Invoke(this, new ParseFailureArgs
8586
{
86-
Cause = exception
87+
Cause = exception,
88+
Component = _component
8789
});
8890
}
8991
catch (SyntaxErrorException exception)
9092
{
9193
_logger.Error(exception, "Exception thrown in thread {0}.", Thread.CurrentThread.ManagedThreadId);
9294
ParseFailure.Invoke(this, new ParseFailureArgs
9395
{
94-
Cause = exception
96+
Cause = exception,
97+
Component = _component
9598
});
9699
}
97100
catch (OperationCanceledException)
@@ -124,6 +127,7 @@ private IEnumerable<CommentNode> QualifyAndUnionComments(QualifiedModuleName qua
124127

125128
public class ParseCompletionArgs
126129
{
130+
public VBComponent Component { get; internal set; }
127131
public ITokenStream Tokens { get; internal set; }
128132
public IParseTree ParseTree { get; internal set; }
129133
public IDictionary<Tuple<string, DeclarationType>, Attributes> Attributes { get; internal set; }
@@ -133,6 +137,7 @@ public class ParseCompletionArgs
133137

134138
public class ParseFailureArgs
135139
{
140+
public VBComponent Component { get; internal set; }
136141
public Exception Cause { get; internal set; }
137142
}
138143

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 112 additions & 76 deletions
Original file line numberDiff line numberDiff line change
@@ -56,8 +56,7 @@ public RubberduckParser(
5656

5757
state.ParseRequest += ReparseRequested;
5858
}
59-
60-
59+
6160
private void ReparseRequested(object sender, ParseRequestEventArgs e)
6261
{
6362
if (e.IsFullReparseRequest)
@@ -140,15 +139,14 @@ private void ParseAll()
140139
var unchanged = components.Where(c => !_state.IsNewOrModified(c)).ToList();
141140

142141
SyncComReferences(projects);
143-
AddBuiltInDeclarations(projects);
142+
AddBuiltInDeclarations();
144143

145144
if (!toParse.Any())
146145
{
147146
State.SetStatusAndFireStateChanged(_state.Status);
148147
return;
149148
}
150149

151-
152150
lock (_state) // note, method is invoked from UI thread... really need the lock here?
153151
{
154152
foreach (var component in toParse)
@@ -160,9 +158,6 @@ private void ParseAll()
160158
// note: seting to 'Parsed' would include them in the resolver walk. 'Ready' excludes them.
161159
_state.SetModuleState(component, ParserState.Ready);
162160
}
163-
164-
Debug.Assert(unchanged.All(component => _state.GetModuleState(component) == ParserState.Ready));
165-
Debug.Assert(toParse.All(component => _state.GetModuleState(component) == ParserState.Pending));
166161
}
167162

168163
// invalidation cleanup should go into ParseAsync?
@@ -171,17 +166,53 @@ private void ParseAll()
171166
_componentAttributes.Remove(invalidated);
172167
}
173168

174-
var parseTasks = toParse.Select(vbComponent => ParseAsync(vbComponent, CancellationToken.None)).ToArray();
175-
Task.WaitAll(parseTasks);
169+
_projectDeclarations.Clear();
170+
_state.ClearBuiltInReferences();
176171

177-
if (_state.Status != ParserState.Error)
172+
var parseTasks = toParse.Select(vbComponent =>
178173
{
179-
Logger.Trace("Starting resolver task");
180-
Resolve(_central.Token);
174+
return Task.Run(() =>
175+
{
176+
ParseAsync(vbComponent, CancellationToken.None);
177+
178+
if (_state.Status == ParserState.Error) { return; }
179+
180+
var parseTree = _state.GetParseTree(vbComponent);
181+
var qualifiedName = _state.ParseTrees.Single(p => p.Value == parseTree).Key;
182+
183+
if (_state.IsNewOrModified(qualifiedName) && !_central.IsCancellationRequested && !_resolverTokenSource.IsCancellationRequested)
184+
{
185+
Logger.Debug("Unmodified module '{0}' resolving", qualifiedName.ComponentName);
186+
ResolveDeclarations(qualifiedName.Component, parseTree);
187+
}
188+
});
189+
})
190+
.ToArray();
191+
192+
Task.WaitAll(parseTasks);
193+
_state.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
194+
195+
if (_state.Status < ParserState.Error && !_central.IsCancellationRequested && !_resolverTokenSource.IsCancellationRequested)
196+
{
197+
// walk all parse trees (modified or not) for identifier references
198+
var finder = new DeclarationFinder(_state.AllDeclarations, _state.AllComments, _state.AllAnnotations);
199+
var passes = new List<ICompilationPass>
200+
{
201+
// This pass has to come first because the type binding resolution depends on it.
202+
new ProjectReferencePass(finder),
203+
new TypeHierarchyPass(finder, new VBAExpressionParser()),
204+
new TypeAnnotationPass(finder, new VBAExpressionParser())
205+
};
206+
207+
passes.ForEach(p => p.Execute());
208+
foreach (var kvp in _state.ParseTrees)
209+
{
210+
Task.Run(() => ResolveReferences(finder, kvp.Key.Component, kvp.Value));
211+
}
181212
}
182213
}
183214

184-
private void AddBuiltInDeclarations(IReadOnlyList<VBProject> projects)
215+
private void AddBuiltInDeclarations()
185216
{
186217
var finder = new DeclarationFinder(_state.AllDeclarations, new CommentNode[] { }, new IAnnotation[] { });
187218
if (finder.MatchName(Tokens.Err).Any(item => item.IsBuiltIn
@@ -283,7 +314,7 @@ private void UnloadComReference(Reference reference, IReadOnlyList<VBProject> pr
283314
if (map == null || !map.IsLoaded)
284315
{
285316
// we're removing a reference we weren't tracking? ...this shouldn't happen.
286-
Debug.Assert(false);
317+
Logger.Error("Unloading untracked COM reference");
287318
return;
288319
}
289320
map.Remove(referencedProjectId);
@@ -294,14 +325,14 @@ private void UnloadComReference(Reference reference, IReadOnlyList<VBProject> pr
294325
}
295326
}
296327

297-
public Task ParseAsync(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null)
328+
private Task ParseAsync(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null)
298329
{
299330
lock (_state)
300-
lock (component)
301-
{
302-
_state.ClearStateCache(component);
303-
_state.SetModuleState(component, ParserState.Pending); // also clears module-exceptions
304-
}
331+
lock (component)
332+
{
333+
_state.ClearStateCache(component);
334+
_state.SetModuleState(component, ParserState.Pending); // also clears module-exceptions
335+
}
305336

306337
var linkedTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_central.Token, token);
307338

@@ -315,76 +346,84 @@ public Task ParseAsync(VBComponent component, CancellationToken token, TokenStre
315346
return task;
316347
}
317348

318-
public void Cancel(VBComponent component = null)
349+
private void Cancel(VBComponent component = null)
319350
{
320351
lock (_central)
321-
lock (_resolverTokenSource)
352+
lock (_resolverTokenSource)
353+
{
354+
if (component == null)
322355
{
323-
if (component == null)
324-
{
325-
_central.Cancel(false);
356+
_central.Cancel(false);
326357

327-
_central.Dispose();
328-
_central = new CancellationTokenSource();
329-
_resolverTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_central.Token);
330-
}
331-
else
332-
{
333-
_resolverTokenSource.Cancel(false);
334-
_resolverTokenSource.Dispose();
358+
_central.Dispose();
359+
_central = new CancellationTokenSource();
360+
_resolverTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_central.Token);
361+
}
362+
else
363+
{
364+
_resolverTokenSource.Cancel(false);
365+
_resolverTokenSource.Dispose();
335366

336-
_resolverTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_central.Token);
337-
Tuple<Task, CancellationTokenSource> result;
338-
if (_currentTasks.TryGetValue(component, out result))
339-
{
340-
result.Item2.Cancel(false);
341-
result.Item2.Dispose();
342-
}
367+
_resolverTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_central.Token);
368+
Tuple<Task, CancellationTokenSource> result;
369+
if (_currentTasks.TryGetValue(component, out result))
370+
{
371+
result.Item2.Cancel(false);
372+
result.Item2.Dispose();
343373
}
344374
}
375+
}
345376
}
346377

347378
private void ParseAsyncInternal(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null)
348379
{
349380
var preprocessor = _preprocessorFactory();
350381
var parser = new ComponentParseTask(component, preprocessor, _attributeParser, rewriter);
351-
parser.ParseFailure += (sender, e) =>
382+
383+
parser.ParseFailure += Parser_ParseFailure;
384+
parser.ParseCompleted += Parser_ParseCompleted;
385+
386+
lock (_state)
387+
lock (component)
352388
{
353-
lock (_state)
354-
lock (component)
355-
{
356-
_state.SetModuleState(component, ParserState.Error, e.Cause as SyntaxErrorException);
357-
}
358-
};
359-
parser.ParseCompleted += (sender, e) =>
389+
_state.SetModuleState(component, ParserState.Parsing);
390+
}
391+
parser.Start(token);
392+
}
393+
394+
private void Parser_ParseCompleted(object sender, ComponentParseTask.ParseCompletionArgs e)
395+
{
396+
lock (_state)
397+
lock (e.Component)
360398
{
361-
lock (_state)
362-
lock (component)
363-
{
364-
_state.SetModuleAttributes(component, e.Attributes);
365-
_state.AddParseTree(component, e.ParseTree);
366-
_state.AddTokenStream(component, e.Tokens);
367-
_state.SetModuleComments(component, e.Comments);
368-
_state.SetModuleAnnotations(component, e.Annotations);
369-
370-
// This really needs to go last
371-
_state.SetModuleState(component, ParserState.Parsed);
372-
}
373-
};
399+
_state.SetModuleAttributes(e.Component, e.Attributes);
400+
_state.AddParseTree(e.Component, e.ParseTree);
401+
_state.AddTokenStream(e.Component, e.Tokens);
402+
_state.SetModuleComments(e.Component, e.Comments);
403+
_state.SetModuleAnnotations(e.Component, e.Annotations);
404+
405+
// This really needs to go last
406+
_state.SetModuleState(e.Component, ParserState.Parsed);
407+
}
408+
409+
((ComponentParseTask)sender).ParseCompleted -= Parser_ParseCompleted;
410+
}
411+
412+
private void Parser_ParseFailure(object sender, ComponentParseTask.ParseFailureArgs e)
413+
{
374414
lock (_state)
375-
lock (component)
376-
{
377-
_state.SetModuleState(component, ParserState.Parsing);
378-
}
379-
parser.Start(token);
415+
lock (e.Component)
416+
{
417+
_state.SetModuleState(e.Component, ParserState.Error, e.Cause as SyntaxErrorException);
418+
}
419+
420+
((ComponentParseTask)sender).ParseFailure -= Parser_ParseFailure;
380421
}
381422

382423
private void Resolve(CancellationToken token)
383424
{
384425
State.SetStatusAndFireStateChanged(ParserState.Resolving);
385426
var sharedTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_resolverTokenSource.Token, token);
386-
// tests expect this to be synchronous :/
387-
//Task.Run(() => ResolveInternal(sharedTokenSource.Token));
388427
ResolveInternal(sharedTokenSource.Token);
389428
}
390429

@@ -397,8 +436,6 @@ private void ResolveInternal(CancellationToken token)
397436
{
398437
return;
399438
}
400-
_projectDeclarations.Clear();
401-
_state.ClearBuiltInReferences();
402439
foreach (var kvp in _state.ParseTrees)
403440
{
404441
var qualifiedName = kvp.Key;
@@ -496,7 +533,7 @@ private void ResolveReferences(DeclarationFinder finder, VBComponent component,
496533
var walker = new ParseTreeWalker();
497534
try
498535
{
499-
Stopwatch watch = Stopwatch.StartNew();
536+
var watch = Stopwatch.StartNew();
500537
walker.Walk(listener, tree);
501538
watch.Stop();
502539
Logger.Debug("Binding Resolution done for component '{0}' in {1}ms (thread {2})", component.Name, watch.ElapsedMilliseconds, Thread.CurrentThread.ManagedThreadId);
@@ -518,15 +555,14 @@ public void Dispose()
518555
{
519556
State.ParseRequest -= ReparseRequested;
520557

521-
if (_central != null)
558+
if (_resolverTokenSource != null)
522559
{
523-
//_central.Cancel();
524-
_central.Dispose();
560+
_resolverTokenSource.Dispose();
525561
}
526562

527-
if (_resolverTokenSource != null)
563+
if (_central != null)
528564
{
529-
_resolverTokenSource.Dispose();
565+
_central.Dispose();
530566
}
531567
}
532568
}

0 commit comments

Comments
 (0)