Skip to content

Commit 3a4c011

Browse files
authored
Merge pull request #1970 from Hosch250/parserCancellationBug
Fix cancellation bug. Don't request reparse on startup--request it w…
2 parents 4ddf2f3 + 55324bd commit 3a4c011

File tree

58 files changed

+629
-582
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

58 files changed

+629
-582
lines changed

RetailCoder.VBE/API/ParserState.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -78,7 +78,7 @@ public void Initialize(VBE vbe)
7878
public void Parse()
7979
{
8080
// blocking call
81-
_parser.Parse();
81+
_parser.Parse(new System.Threading.CancellationTokenSource());
8282
}
8383

8484
/// <summary>

RetailCoder.VBE/App.cs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,6 @@
1111
using Rubberduck.UI.Command.MenuItems;
1212
using System;
1313
using System.Globalization;
14-
using System.Threading.Tasks;
1514
using System.Windows.Forms;
1615

1716
namespace Rubberduck
@@ -141,7 +140,6 @@ public void Startup()
141140
_appMenus.Initialize();
142141
_hooks.HookHotkeys(); // need to hook hotkeys before we localize menus, to correctly display ShortcutTexts
143142
_appMenus.Localize();
144-
Task.Delay(1000).ContinueWith(t => UiDispatcher.Invoke(() => _parser.State.OnParseRequested(this)));
145143
UpdateLoggingLevel();
146144
}
147145

Rubberduck.Parsing/Symbols/DeclarationSymbolsListener.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,6 @@
99
using System.Collections.Generic;
1010
using System.Linq;
1111
using System.Runtime.InteropServices;
12-
using Antlr4.Runtime.Misc;
1312

1413
namespace Rubberduck.Parsing.Symbols
1514
{
@@ -801,8 +800,8 @@ public override void ExitPrivateTypeDeclaration(VBAParser.PrivateTypeDeclaration
801800
{
802801
_parentDeclaration = _moduleDeclaration;
803802
}
804-
805-
public void AddUdtDeclaration(VBAParser.UdtDeclarationContext udtDeclaration, Accessibility accessibility, ParserRuleContext context)
803+
804+
private void AddUdtDeclaration(VBAParser.UdtDeclarationContext udtDeclaration, Accessibility accessibility, ParserRuleContext context)
806805
{
807806
var identifier = Identifier.GetName(udtDeclaration.untypedIdentifier());
808807
var identifierSelection = Identifier.GetNameSelection(udtDeclaration.untypedIdentifier());

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 60 additions & 59 deletions
Original file line numberDiff line numberDiff line change
@@ -20,9 +20,7 @@ namespace Rubberduck.Parsing.VBA
2020
public class RubberduckParser : IRubberduckParser
2121
{
2222
public RubberduckParserState State { get { return _state; } }
23-
24-
private CancellationTokenSource _central = new CancellationTokenSource();
25-
private CancellationTokenSource _resolverTokenSource; // linked to _central later
23+
2624
private readonly ConcurrentDictionary<VBComponent, Tuple<Task, CancellationTokenSource>> _currentTasks =
2725
new ConcurrentDictionary<VBComponent, Tuple<Task, CancellationTokenSource>>();
2826

@@ -43,7 +41,6 @@ public RubberduckParser(
4341
Func<IVBAPreprocessor> preprocessorFactory,
4442
IEnumerable<ICustomDeclarationLoader> customDeclarationLoaders)
4543
{
46-
_resolverTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_central.Token);
4744
_vbe = vbe;
4845
_state = state;
4946
_attributeParser = attributeParser;
@@ -53,12 +50,17 @@ public RubberduckParser(
5350
state.ParseRequest += ReparseRequested;
5451
}
5552

53+
// Do not access this from anywhere but ReparseRequested.
54+
// ReparseRequested needs to have a reference to all the cancellation tokens,
55+
// but the cancelees need to use their own token.
56+
private readonly List<CancellationTokenSource> _cancellationTokens = new List<CancellationTokenSource> {new CancellationTokenSource()};
57+
5658
private void ReparseRequested(object sender, ParseRequestEventArgs e)
5759
{
5860
if (e.IsFullReparseRequest)
5961
{
6062
Cancel();
61-
Task.Run(() => ParseAll());
63+
Task.Run(() => ParseAll(_cancellationTokens[0]));
6264
}
6365
else
6466
{
@@ -70,14 +72,14 @@ private void ReparseRequested(object sender, ParseRequestEventArgs e)
7072
SyncComReferences(State.Projects);
7173
AddBuiltInDeclarations();
7274

73-
if (_resolverTokenSource.IsCancellationRequested || _central.IsCancellationRequested)
75+
if (_cancellationTokens[0].IsCancellationRequested)
7476
{
7577
return;
7678
}
7779

78-
ParseAsync(e.Component, CancellationToken.None).Wait();
80+
ParseAsync(e.Component, _cancellationTokens[0]).Wait();
7981

80-
if (_resolverTokenSource.IsCancellationRequested || _central.IsCancellationRequested)
82+
if (_cancellationTokens[0].IsCancellationRequested)
8183
{
8284
return;
8385
}
@@ -93,7 +95,7 @@ private void ReparseRequested(object sender, ParseRequestEventArgs e)
9395
if (State.Status < ParserState.Error)
9496
{
9597
State.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
96-
ResolveReferencesAsync();
98+
ResolveReferencesAsync(_cancellationTokens[0].Token);
9799
}
98100
});
99101
}
@@ -102,7 +104,7 @@ private void ReparseRequested(object sender, ParseRequestEventArgs e)
102104
/// <summary>
103105
/// For the use of tests only
104106
/// </summary>
105-
public void Parse()
107+
public void Parse(CancellationTokenSource token)
106108
{
107109
if (State.Projects.Count == 0)
108110
{
@@ -153,9 +155,9 @@ public void Parse()
153155
var index = i;
154156
parseTasks[i] = new Task(() =>
155157
{
156-
ParseAsync(components[index], CancellationToken.None).Wait();
158+
ParseAsync(components[index], token).Wait(token.Token);
157159

158-
if (_resolverTokenSource.IsCancellationRequested || _central.IsCancellationRequested)
160+
if (token.IsCancellationRequested)
159161
{
160162
return;
161163
}
@@ -177,14 +179,14 @@ public void Parse()
177179
if (State.Status < ParserState.Error)
178180
{
179181
State.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
180-
Task.WaitAll(ResolveReferencesAsync());
182+
Task.WaitAll(ResolveReferencesAsync(token.Token));
181183
}
182184
}
183185

184186
/// <summary>
185187
/// Starts parsing all components of all unprotected VBProjects associated with the VBE-Instance passed to the constructor of this parser instance.
186188
/// </summary>
187-
private void ParseAll()
189+
private void ParseAll(CancellationTokenSource token)
188190
{
189191
if (State.Projects.Count == 0)
190192
{
@@ -230,18 +232,13 @@ private void ParseAll()
230232
}
231233

232234
var toParse = new List<VBComponent>();
233-
var unchanged = new List<VBComponent>();
234235

235236
foreach (var component in components)
236237
{
237238
if (State.IsNewOrModified(component))
238239
{
239240
toParse.Add(component);
240241
}
241-
else
242-
{
243-
unchanged.Add(component);
244-
}
245242
}
246243

247244
if (toParse.Count == 0)
@@ -272,6 +269,11 @@ private void ParseAll()
272269
}
273270
}
274271

272+
if (token.IsCancellationRequested)
273+
{
274+
return;
275+
}
276+
275277
_projectDeclarations.Clear();
276278
State.ClearBuiltInReferences();
277279

@@ -281,9 +283,9 @@ private void ParseAll()
281283
var index = i;
282284
parseTasks[i] = new Task(() =>
283285
{
284-
ParseAsync(toParse[index], CancellationToken.None).Wait();
286+
ParseAsync(toParse[index], token).Wait(token.Token);
285287

286-
if (_resolverTokenSource.IsCancellationRequested || _central.IsCancellationRequested)
288+
if (token.IsCancellationRequested)
287289
{
288290
return;
289291
}
@@ -301,16 +303,21 @@ private void ParseAll()
301303
parseTasks[i].Start();
302304
}
303305

306+
if (token.IsCancellationRequested)
307+
{
308+
return;
309+
}
310+
304311
Task.WaitAll(parseTasks);
305312

306313
if (State.Status < ParserState.Error)
307314
{
308315
State.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
309-
ResolveReferencesAsync();
316+
ResolveReferencesAsync(token.Token);
310317
}
311318
}
312319

313-
private Task[] ResolveReferencesAsync()
320+
private Task[] ResolveReferencesAsync(CancellationToken token)
314321
{
315322
var finder = new DeclarationFinder(State.AllDeclarations, State.AllComments, State.AllAnnotations);
316323
var passes = new List<ICompilationPass>
@@ -327,7 +334,7 @@ private Task[] ResolveReferencesAsync()
327334
for (var index = 0; index < State.ParseTrees.Count; index++)
328335
{
329336
var kvp = State.ParseTrees[index];
330-
if (_resolverTokenSource.IsCancellationRequested || _central.IsCancellationRequested)
337+
if (token.IsCancellationRequested)
331338
{
332339
return new Task[0];
333340
}
@@ -337,7 +344,7 @@ private Task[] ResolveReferencesAsync()
337344
State.SetModuleState(kvp.Key.Component, ParserState.ResolvingReferences);
338345

339346
ResolveReferences(finder, kvp.Key.Component, kvp.Value);
340-
});
347+
}, token);
341348
}
342349

343350
return tasks;
@@ -489,49 +496,44 @@ private void UnloadComReference(Reference reference, IReadOnlyList<VBProject> pr
489496
}
490497
}
491498

492-
private Task ParseAsync(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null)
499+
private Task ParseAsync(VBComponent component, CancellationTokenSource token, TokenStreamRewriter rewriter = null)
493500
{
494501
State.ClearStateCache(component);
495502

496-
var linkedTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_central.Token, token);
497-
498-
var task = new Task(() => ParseAsyncInternal(component, linkedTokenSource.Token, rewriter));
499-
_currentTasks.TryAdd(component, Tuple.Create(task, linkedTokenSource));
503+
var task = new Task(() => ParseAsyncInternal(component, token.Token, rewriter));
504+
_currentTasks.TryAdd(component, Tuple.Create(task, token));
500505

501506
Tuple<Task, CancellationTokenSource> removedTask;
502-
task.ContinueWith(t => _currentTasks.TryRemove(component, out removedTask)); // default also executes on cancel
507+
task.ContinueWith(t => _currentTasks.TryRemove(component, out removedTask), token.Token); // default also executes on cancel
503508
// See http://stackoverflow.com/questions/6800705/why-is-taskscheduler-current-the-default-taskscheduler
504509
task.Start(TaskScheduler.Default);
505510
return task;
506511
}
507512

508513
public void Cancel(VBComponent component = null)
509514
{
510-
lock (_central)
511-
lock (_resolverTokenSource)
515+
lock (_cancellationTokens[0])
516+
{
517+
if (component == null)
512518
{
513-
if (component == null)
514-
{
515-
_central.Cancel(false);
519+
_cancellationTokens[0].Cancel();
516520

517-
_central.Dispose();
518-
_central = new CancellationTokenSource();
519-
_resolverTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_central.Token);
520-
}
521-
else
521+
_cancellationTokens[0].Dispose();
522+
_cancellationTokens.Add(new CancellationTokenSource());
523+
_cancellationTokens.RemoveAt(0);
524+
}
525+
else
526+
{
527+
_cancellationTokens[0].Cancel();
528+
529+
Tuple<Task, CancellationTokenSource> result;
530+
if (_currentTasks.TryGetValue(component, out result))
522531
{
523-
_resolverTokenSource.Cancel(false);
524-
_resolverTokenSource.Dispose();
525-
526-
_resolverTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_central.Token);
527-
Tuple<Task, CancellationTokenSource> result;
528-
if (_currentTasks.TryGetValue(component, out result))
529-
{
530-
result.Item2.Cancel(false);
531-
result.Item2.Dispose();
532-
}
532+
result.Item2.Cancel();
533+
result.Item2.Dispose();
533534
}
534535
}
536+
}
535537
}
536538

537539
private void ParseAsyncInternal(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null)
@@ -569,6 +571,7 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
569571

570572
var qualifiedModuleName = new QualifiedModuleName(component);
571573

574+
var stopwatch = Stopwatch.StartNew();
572575
try
573576
{
574577
var project = component.Collection.Parent;
@@ -581,6 +584,7 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
581584
State.AddDeclaration(projectDeclaration);
582585
}
583586
Logger.Debug("Creating declarations for module {0}.", qualifiedModuleName.Name);
587+
584588
var declarationsListener = new DeclarationSymbolsListener(State, qualifiedModuleName, component.Type, State.GetModuleAnnotations(component), State.GetModuleAttributes(component), projectDeclaration);
585589
ParseTreeWalker.Default.Walk(declarationsListener, tree);
586590
foreach (var createdDeclaration in declarationsListener.CreatedDeclarations)
@@ -593,6 +597,8 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
593597
Logger.Error(exception, "Exception thrown acquiring declarations for '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
594598
State.SetModuleState(component, ParserState.ResolverError);
595599
}
600+
stopwatch.Stop();
601+
Logger.Debug("{0}ms to resolve declarations for component {1}", stopwatch.ElapsedMilliseconds, component.Name);
596602
}
597603

598604
private Declaration CreateProjectDeclaration(QualifiedModuleName projectQualifiedName, VBProject project)
@@ -654,15 +660,10 @@ public void Dispose()
654660
{
655661
State.ParseRequest -= ReparseRequested;
656662

657-
if (_central != null)
658-
{
659-
//_central.Cancel();
660-
_central.Dispose();
661-
}
662-
663-
if (_resolverTokenSource != null)
663+
if (_cancellationTokens[0] != null)
664664
{
665-
_resolverTokenSource.Dispose();
665+
_cancellationTokens[0].Cancel();
666+
_cancellationTokens[0].Dispose();
666667
}
667668
}
668669
}

RubberduckTests/Binding/IndexDefaultBindingTests.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using Rubberduck.Parsing.VBA;
55
using RubberduckTests.Mocks;
66
using System.Linq;
7+
using System.Threading;
78
using Moq;
89
using Rubberduck.Parsing;
910

@@ -86,7 +87,7 @@ End Property
8687
private static RubberduckParserState Parse(Moq.Mock<VBE> vbe)
8788
{
8889
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object, new Mock<ISinks>().Object));
89-
parser.Parse();
90+
parser.Parse(new CancellationTokenSource());
9091
if (parser.State.Status != ParserState.Ready)
9192
{
9293
Assert.Inconclusive("Parser state should be 'Ready', but returns '{0}'.", parser.State.Status);

RubberduckTests/Binding/MemberAccessDefaultBindingTests.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
using RubberduckTests.Mocks;
66
using System;
77
using System.Linq;
8+
using System.Threading;
89
using Moq;
910
using Rubberduck.Parsing;
1011

@@ -95,7 +96,7 @@ public void LExpressionIsEnum()
9596
private static RubberduckParserState Parse(Moq.Mock<VBE> vbe)
9697
{
9798
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object, new Mock<ISinks>().Object));
98-
parser.Parse();
99+
parser.Parse(new CancellationTokenSource());
99100
if (parser.State.Status != ParserState.Ready)
100101
{
101102
Assert.Inconclusive("Parser state should be 'Ready', but returns '{0}'.", parser.State.Status);

RubberduckTests/Binding/MemberAccessProcedurePointerBindingTests.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
using System.Linq;
88
using Moq;
99
using Rubberduck.Parsing;
10+
using System.Threading;
1011

1112
namespace RubberduckTests.Binding
1213
{
@@ -40,7 +41,7 @@ public void ProceduralModuleWithAccessibleMember()
4041
private static RubberduckParserState Parse(Moq.Mock<VBE> vbe)
4142
{
4243
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object, new Mock<ISinks>().Object));
43-
parser.Parse();
44+
parser.Parse(new CancellationTokenSource());
4445
if (parser.State.Status != ParserState.Ready)
4546
{
4647
Assert.Inconclusive("Parser state should be 'Ready', but returns '{0}'.", parser.State.Status);

0 commit comments

Comments
 (0)