Skip to content

Commit 0d5cc6b

Browse files
committed
Introduced option not to eval parser state on module state change and introduced method to trigger the evaluation manually. Moreover, made changing all module states concurrent.
1 parent 3fe56a2 commit 0d5cc6b

File tree

2 files changed

+29
-11
lines changed

2 files changed

+29
-11
lines changed

Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 16 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ public class ParseCoordinator : IParseCoordinator
2828
public RubberduckParserState State { get { return _state; } }
2929

3030
private const int _maxDegreeOfParserParallelism = -1;
31+
private const int _maxDegreeOfModuleStateChangeParallelism = -1;
3132

3233
private readonly IDictionary<IVBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>> _componentAttributes
3334
= new Dictionary<IVBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>>();
@@ -163,10 +164,12 @@ private void RefreshDeclarationFinder()
163164

164165
private void SetModuleStates(List<IVBComponent> components, ParserState parserState)
165166
{
166-
foreach (var component in components)
167-
{
168-
State.SetModuleState(component, parserState);
169-
}
167+
var options = new ParallelOptions();
168+
options.MaxDegreeOfParallelism = _maxDegreeOfModuleStateChangeParallelism;
169+
170+
Parallel.ForEach(components, options, component => State.SetModuleState(component, parserState, null, false));
171+
172+
State.EvaluateParserState();
170173
}
171174

172175
private void CleanUpComponentAttributes(List<IVBComponent> components)
@@ -190,6 +193,8 @@ private void ClearComponentStateCacheForTests()
190193

191194
private void ParseComponents(List<IVBComponent> components, CancellationToken token)
192195
{
196+
SetModuleStates(components, ParserState.Parsing);
197+
193198
var options = new ParallelOptions();
194199
options.CancellationToken = token;
195200
options.MaxDegreeOfParallelism = _maxDegreeOfParserParallelism;
@@ -198,12 +203,12 @@ private void ParseComponents(List<IVBComponent> components, CancellationToken to
198203
options,
199204
component =>
200205
{
201-
State.SetModuleState(component, ParserState.Parsing);
202206
State.ClearStateCache(component);
203207
var finishedParseTask = FinishedParseComponentTask(component, token);
204208
ProcessComponentParseResults(component, finishedParseTask);
205209
}
206210
);
211+
State.EvaluateParserState();
207212
}
208213

209214
private Task<ComponentParseTask.ParseCompletionArgs> FinishedParseComponentTask(IVBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null)
@@ -233,6 +238,7 @@ private void ProcessComponentParseResults(IVBComponent component, Task<Component
233238
finishedParseTask.Wait();
234239
if (finishedParseTask.IsFaulted)
235240
{
241+
//In contrast to the situation in the success scenario, the overall parser state is reevaluated immediately.
236242
State.SetModuleState(component, ParserState.Error, finishedParseTask.Exception.InnerException as SyntaxErrorException);
237243
}
238244
else if (finishedParseTask.IsCompleted)
@@ -249,7 +255,9 @@ private void ProcessComponentParseResults(IVBComponent component, Task<Component
249255
State.SetModuleAnnotations(component, result.Annotations);
250256

251257
// This really needs to go last
252-
State.SetModuleState(component, ParserState.Parsed);
258+
//It does not reevaluate the overall parer state to avoid concurrent evaluation of all module states and for performance reasons.
259+
//The evaluation has to be triggered manually in the calling procedure.
260+
State.SetModuleState(component, ParserState.Parsed, null, false);
253261
}
254262
}
255263
}
@@ -258,6 +266,8 @@ private void ProcessComponentParseResults(IVBComponent component, Task<Component
258266

259267
private void ResolveAllDeclarations(List<IVBComponent> components, CancellationToken token)
260268
{
269+
SetModuleStates(components, ParserState.ResolvingDeclarations);
270+
261271
var options = new ParallelOptions();
262272
options.CancellationToken = token;
263273
options.MaxDegreeOfParallelism = _maxDegreeOfParserParallelism;
@@ -267,7 +277,6 @@ private void ResolveAllDeclarations(List<IVBComponent> components, CancellationT
267277
component =>
268278
{
269279
var qualifiedName = new QualifiedModuleName(component);
270-
State.SetModuleState(component, ParserState.ResolvingDeclarations);
271280
ResolveDeclarations(qualifiedName.Component,
272281
State.ParseTrees.Find(s => s.Key == qualifiedName).Value);
273282
}

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 13 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -311,7 +311,7 @@ private void OnModuleStateChanged(IVBComponent component, ParserState state, Par
311311
}
312312
}
313313

314-
public void SetModuleState(IVBComponent component, ParserState state, SyntaxErrorException parserError = null)
314+
public void SetModuleState(IVBComponent component, ParserState state, SyntaxErrorException parserError = null, bool evaluateOverallState = true)
315315
{
316316
if (AllUserDeclarations.Count > 0)
317317
{
@@ -339,7 +339,7 @@ public void SetModuleState(IVBComponent component, ParserState state, SyntaxErro
339339
{
340340
// ghost component shouldn't even exist
341341
ClearStateCache(component);
342-
Status = EvaluateParserState();
342+
EvaluateParserState();
343343
return;
344344
}
345345
}
@@ -351,10 +351,18 @@ public void SetModuleState(IVBComponent component, ParserState state, SyntaxErro
351351
_moduleStates.AddOrUpdate(key, new ModuleState(parserError), (c, e) => e.SetModuleException(parserError));
352352
Logger.Debug("Module '{0}' state is changing to '{1}' (thread {2})", key.ComponentName, state, Thread.CurrentThread.ManagedThreadId);
353353
OnModuleStateChanged(component, state, oldState);
354-
Status = EvaluateParserState();
354+
if (evaluateOverallState)
355+
{
356+
EvaluateParserState();
357+
}
358+
}
359+
360+
public void EvaluateParserState()
361+
{
362+
lock (_statusLockObject) Status = OverallParserStateFromModuleStates();
355363
}
356364

357-
private ParserState EvaluateParserState()
365+
private ParserState OverallParserStateFromModuleStates()
358366
{
359367
if (_moduleStates.IsEmpty)
360368
{
@@ -497,6 +505,7 @@ public ParserState GetModuleState(IVBComponent component)
497505
return _moduleStates.GetOrAdd(new QualifiedModuleName(component), new ModuleState(ParserState.Pending)).State;
498506
}
499507

508+
private readonly object _statusLockObject = new object();
500509
private ParserState _status;
501510
public ParserState Status
502511
{

0 commit comments

Comments
 (0)