Skip to content

Commit 35b5961

Browse files
committed
Use only 1 parser and add event to parser state to trigger a parse from anywhere.
1 parent 2939433 commit 35b5961

File tree

5 files changed

+86
-73
lines changed

5 files changed

+86
-73
lines changed

RetailCoder.VBE/App.cs

Lines changed: 3 additions & 70 deletions
Original file line numberDiff line numberDiff line change
@@ -36,9 +36,6 @@ public class App : IDisposable
3636

3737
private Configuration _config;
3838

39-
private readonly ConcurrentDictionary<VBComponent, CancellationTokenSource> _tokenSources =
40-
new ConcurrentDictionary<VBComponent, CancellationTokenSource>();
41-
4239
public App(VBE vbe, IMessageBox messageBox,
4340
IParserErrorsPresenterFactory parserErrorsPresenterFactory,
4441
IRubberduckParser parser,
@@ -94,7 +91,7 @@ private async void hooks_MessageReceived(object sender, HookEventArgs e)
9491
}
9592

9693
var component = _vbe.ActiveCodePane.CodeModule.Parent;
97-
ParseComponentAsync(component);
94+
_parser.ParseComponentAsync(component);
9895

9996
AwaitNextKey();
10097
return;
@@ -141,48 +138,14 @@ private async void hooks_MessageReceived(object sender, HookEventArgs e)
141138

142139
private void _stateBar_Refresh(object sender, EventArgs e)
143140
{
144-
ParseAll();
141+
_parser.State.RequestParse();
145142
}
146143

147144
private void Parser_StateChanged(object sender, EventArgs e)
148145
{
149146
_appMenus.EvaluateCanExecute(_parser.State);
150147
}
151148

152-
private void ParseComponentAsync(VBComponent component, bool resolve = true)
153-
{
154-
var tokenSource = RenewTokenSource(component);
155-
156-
var token = tokenSource.Token;
157-
_parser.ParseAsync(component, token);
158-
159-
if (resolve && !token.IsCancellationRequested)
160-
{
161-
using (var source = new CancellationTokenSource())
162-
{
163-
_parser.Resolve(source.Token);
164-
}
165-
}
166-
}
167-
168-
private CancellationTokenSource RenewTokenSource(VBComponent component)
169-
{
170-
if (_tokenSources.ContainsKey(component))
171-
{
172-
CancellationTokenSource existingTokenSource;
173-
_tokenSources.TryRemove(component, out existingTokenSource);
174-
if (existingTokenSource != null)
175-
{
176-
existingTokenSource.Cancel();
177-
existingTokenSource.Dispose();
178-
}
179-
}
180-
181-
var tokenSource = new CancellationTokenSource();
182-
_tokenSources[component] = tokenSource;
183-
return tokenSource;
184-
}
185-
186149
public void Startup()
187150
{
188151
CleanReloadConfig();
@@ -193,36 +156,15 @@ public void Startup()
193156
Task.Delay(1000).ContinueWith(t =>
194157
{
195158
_parser.State.AddBuiltInDeclarations(_vbe.HostApplication());
196-
ParseAll();
159+
_parser.State.RequestParse();
197160
});
198161

199-
Task.Delay(1000).ContinueWith(t =>
200-
{
201-
_hooks.AddHook(new LowLevelKeyboardHook(_vbe));
202-
_hooks.Attach();
203-
});
204162
//_hooks.AddHook(new LowLevelKeyboardHook(_vbe));
205163
//_hooks.AddHook(new HotKey((IntPtr)_vbe.MainWindow.HWnd, "%^R", Keys.R));
206164
//_hooks.AddHook(new HotKey((IntPtr)_vbe.MainWindow.HWnd, "%^I", Keys.I));
207165
//_hooks.Attach();
208166
}
209167

210-
private void ParseAll()
211-
{
212-
var components = _vbe.VBProjects.Cast<VBProject>()
213-
.SelectMany(project => project.VBComponents.Cast<VBComponent>());
214-
215-
var result = Parallel.ForEach(components, component => { ParseComponentAsync(component, false); });
216-
217-
if (result.IsCompleted)
218-
{
219-
using (var tokenSource = new CancellationTokenSource())
220-
{
221-
_parser.Resolve(tokenSource.Token);
222-
}
223-
}
224-
}
225-
226168
private void CleanReloadConfig()
227169
{
228170
LoadConfig();
@@ -267,15 +209,6 @@ public void Dispose()
267209
_parser.State.StateChanged -= Parser_StateChanged;
268210

269211
_hooks.Dispose();
270-
271-
if (_tokenSources.Any())
272-
{
273-
foreach (var tokenSource in _tokenSources)
274-
{
275-
tokenSource.Value.Cancel();
276-
tokenSource.Value.Dispose();
277-
}
278-
}
279212
}
280213
}
281214
}

RetailCoder.VBE/Root/RubberduckModule.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -61,6 +61,7 @@ public override void Load()
6161
Rebind<IIndenter>().To<Indenter>().InSingletonScope();
6262
Rebind<IIndenterSettings>().To<IndenterSettings>();
6363
Bind<TestExplorerModelBase>().To<StandardModuleTestExplorerModel>().InSingletonScope();
64+
Rebind<IRubberduckParser>().To<RubberduckParser>().InSingletonScope();
6465

6566
Bind<IPresenter>().To<TestExplorerDockablePresenter>()
6667
.WhenInjectedInto<TestExplorerCommand>()

Rubberduck.Parsing/IRubberduckParser.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ namespace Rubberduck.Parsing
88
public interface IRubberduckParser
99
{
1010
RubberduckParserState State { get; }
11+
void ParseComponentAsync(VBComponent component, bool resolve = true);
1112
Task ParseAsync(VBComponent component, CancellationToken token);
1213
void Resolve(CancellationToken token);
1314
}

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 64 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,13 @@
11
using System;
2+
using System.Collections.Concurrent;
23
using System.Collections.Generic;
34
using System.Linq;
4-
using System.Runtime.InteropServices;
55
using System.Text;
66
using System.Threading;
77
using System.Threading.Tasks;
88
using Antlr4.Runtime;
99
using Antlr4.Runtime.Tree;
1010
using Microsoft.Vbe.Interop;
11-
using NLog;
1211
using Rubberduck.Parsing.Grammar;
1312
using Rubberduck.Parsing.Nodes;
1413
using Rubberduck.Parsing.Symbols;
@@ -20,14 +19,76 @@ namespace Rubberduck.Parsing.VBA
2019
{
2120
public class RubberduckParser : IRubberduckParser
2221
{
23-
public RubberduckParser(RubberduckParserState state)
22+
public RubberduckParser(VBE vbe, RubberduckParserState state)
2423
{
24+
_vbe = vbe;
2525
_state = state;
26+
27+
state.ParseRequest += state_ParseRequest;
28+
}
29+
30+
void state_ParseRequest()
31+
{
32+
ParseAll();
2633
}
2734

35+
private readonly VBE _vbe;
2836
private readonly RubberduckParserState _state;
2937
public RubberduckParserState State { get { return _state; } }
3038

39+
private readonly ConcurrentDictionary<VBComponent, CancellationTokenSource> _tokenSources =
40+
new ConcurrentDictionary<VBComponent, CancellationTokenSource>();
41+
42+
public void ParseComponentAsync(VBComponent component, bool resolve = true)
43+
{
44+
var tokenSource = RenewTokenSource(component);
45+
46+
var token = tokenSource.Token;
47+
ParseAsync(component, token);
48+
49+
if (resolve && !token.IsCancellationRequested)
50+
{
51+
using (var source = new CancellationTokenSource())
52+
{
53+
Resolve(source.Token);
54+
}
55+
}
56+
}
57+
58+
private CancellationTokenSource RenewTokenSource(VBComponent component)
59+
{
60+
if (_tokenSources.ContainsKey(component))
61+
{
62+
CancellationTokenSource existingTokenSource;
63+
_tokenSources.TryRemove(component, out existingTokenSource);
64+
if (existingTokenSource != null)
65+
{
66+
existingTokenSource.Cancel();
67+
existingTokenSource.Dispose();
68+
}
69+
}
70+
71+
var tokenSource = new CancellationTokenSource();
72+
_tokenSources[component] = tokenSource;
73+
return tokenSource;
74+
}
75+
76+
private void ParseAll()
77+
{
78+
var components = _vbe.VBProjects.Cast<VBProject>()
79+
.SelectMany(project => project.VBComponents.Cast<VBComponent>());
80+
81+
var result = Parallel.ForEach(components, component => { ParseComponentAsync(component, false); });
82+
83+
if (result.IsCompleted)
84+
{
85+
using (var tokenSource = new CancellationTokenSource())
86+
{
87+
Resolve(tokenSource.Token);
88+
}
89+
}
90+
}
91+
3192
public Task ParseAsync(VBComponent vbComponent, CancellationToken token)
3293
{
3394
var component = vbComponent;

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,9 @@ public enum ResolutionState
1818

1919
public class RubberduckParserState
2020
{
21+
public delegate void ParseRequestEventHandler();
22+
public event ParseRequestEventHandler ParseRequest;
23+
2124
// keys are the declarations; values indicate whether a declaration is resolved.
2225
private readonly ConcurrentDictionary<Declaration, ResolutionState> _declarations =
2326
new ConcurrentDictionary<Declaration, ResolutionState>();
@@ -192,5 +195,19 @@ public void AddBuiltInDeclarations(IHostApplication hostApplication)
192195
AddDeclaration(declaration);
193196
}
194197
}
198+
199+
public void RequestParse()
200+
{
201+
OnParseRequest();
202+
}
203+
204+
protected virtual void OnParseRequest()
205+
{
206+
var handler = ParseRequest;
207+
if (handler != null)
208+
{
209+
handler();
210+
}
211+
}
195212
}
196213
}

0 commit comments

Comments
 (0)