Skip to content

Commit 6cccf0c

Browse files
authored
Merge branch 'next' into next
2 parents 89ec001 + 9270b63 commit 6cccf0c

File tree

4 files changed

+38
-48
lines changed

4 files changed

+38
-48
lines changed

RetailCoder.VBE/App.cs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -225,6 +225,8 @@ async void sink_ProjectRemoved(object sender, DispatcherEventArgs<VBProject> e)
225225
return;
226226
}
227227

228+
_parser.Cancel();
229+
228230
var projectId = e.Item.HelpFile;
229231
Debug.Assert(projectId != null);
230232

@@ -334,6 +336,8 @@ async void sink_ComponentRenamed(object sender, DispatcherRenamedEventArgs<VBCom
334336
return;
335337
}
336338

339+
_parser.Cancel();
340+
337341
_sourceControlPanelVM.HandleRenamedComponent(e.Item, e.OldName);
338342

339343
_logger.Debug("Component '{0}' was renamed to '{1}'.", e.OldName, e.Item.Name);
@@ -389,6 +393,8 @@ async void sink_ComponentRemoved(object sender, DispatcherEventArgs<VBComponent>
389393
return;
390394
}
391395

396+
_parser.Cancel(e.Item);
397+
392398
_sourceControlPanelVM.HandleRemovedComponent(e.Item);
393399

394400
_logger.Debug("Component '{0}' was removed.", e.Item.Name);
@@ -404,6 +410,8 @@ async void sink_ComponentReloaded(object sender, DispatcherEventArgs<VBComponent
404410
return;
405411
}
406412

413+
_parser.Cancel(e.Item);
414+
407415
_logger.Debug("Component '{0}' was reloaded.", e.Item.Name);
408416
_parser.State.OnParseRequested(sender, e.Item);
409417
}
@@ -445,6 +453,8 @@ async void sink_ProjectRenamed(object sender, DispatcherRenamedEventArgs<VBProje
445453
return;
446454
}
447455

456+
_parser.Cancel();
457+
448458
_logger.Debug("Project '{0}' (ID {1}) was renamed to '{2}'.", e.OldName, e.Item.HelpFile, e.Item.Name);
449459

450460
_parser.State.RemoveProject(e.Item.HelpFile);

Rubberduck.Parsing/Binding/TypeBindingContext.cs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,13 @@ private IExpressionBinding Visit(Declaration module, Declaration parent, VBAPars
4444
return Visit(module, parent, lexpr);
4545
}
4646

47+
private IExpressionBinding Visit(Declaration module, Declaration parent, VBAParser.IndexExprContext expression)
48+
{
49+
dynamic lexpr = expression.lExpression();
50+
var type = expression.lExpression().GetType();
51+
return Visit(module, parent, lexpr);
52+
}
53+
4754
private IExpressionBinding Visit(Declaration module, Declaration parent, VBAParser.SimpleNameExprContext expression)
4855
{
4956
return new SimpleNameTypeBinding(_declarationFinder, Declaration.GetProjectParent(parent), module, parent, expression);
Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,12 @@
11
using System;
2+
using Microsoft.Vbe.Interop;
23
using Rubberduck.Parsing.VBA;
34

45
namespace Rubberduck.Parsing
56
{
67
public interface IRubberduckParser : IDisposable
78
{
89
RubberduckParserState State { get; }
10+
void Cancel(VBComponent component = null);
911
}
1012
}

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 19 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -260,17 +260,14 @@ private void ParseAll()
260260
return;
261261
}
262262

263-
lock (State) // note, method is invoked from UI thread... really need the lock here?
263+
foreach (var component in toParse)
264264
{
265-
foreach (var component in toParse)
266-
{
267-
State.SetModuleState(component, ParserState.Pending);
268-
}
269-
foreach (var component in unchanged)
270-
{
271-
// note: seting to 'Parsed' would include them in the resolver walk. 'Ready' excludes them.
272-
State.SetModuleState(component, ParserState.Ready);
273-
}
265+
State.SetModuleState(component, ParserState.Pending);
266+
}
267+
foreach (var component in unchanged)
268+
{
269+
// note: seting to 'Parsed' would include them in the resolver walk. 'Ready' excludes them.
270+
State.SetModuleState(component, ParserState.Ready);
274271
}
275272

276273
// invalidation cleanup should go into ParseAsync?
@@ -304,10 +301,7 @@ private void ParseAll()
304301
Logger.Debug("Module '{0}' {1}", qualifiedName.ComponentName,
305302
State.IsNewOrModified(qualifiedName) ? "was modified" : "was NOT modified");
306303

307-
lock (State)
308-
{
309-
State.SetModuleState(toParse[index], ParserState.ResolvingDeclarations);
310-
}
304+
State.SetModuleState(toParse[index], ParserState.ResolvingDeclarations);
311305

312306
ResolveDeclarations(qualifiedName.Component,
313307
State.ParseTrees.Find(s => s.Key == qualifiedName).Value);
@@ -349,10 +343,7 @@ private Task[] ResolveReferencesAsync()
349343

350344
tasks[index] = Task.Run(() =>
351345
{
352-
lock (State)
353-
{
354-
State.SetModuleState(kvp.Key.Component, ParserState.ResolvingReferences);
355-
}
346+
State.SetModuleState(kvp.Key.Component, ParserState.ResolvingReferences);
356347

357348
ResolveReferences(finder, kvp.Key.Component, kvp.Value);
358349
});
@@ -363,14 +354,11 @@ private Task[] ResolveReferencesAsync()
363354

364355
private void AddBuiltInDeclarations()
365356
{
366-
lock (State)
357+
foreach (var customDeclarationLoader in _customDeclarationLoaders)
367358
{
368-
foreach (var customDeclarationLoader in _customDeclarationLoaders)
359+
foreach (var declaration in customDeclarationLoader.Load())
369360
{
370-
foreach (var declaration in customDeclarationLoader.Load())
371-
{
372-
State.AddDeclaration(declaration);
373-
}
361+
State.AddDeclaration(declaration);
374362
}
375363
}
376364
}
@@ -512,12 +500,8 @@ private void UnloadComReference(Reference reference, IReadOnlyList<VBProject> pr
512500

513501
private Task ParseAsync(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null)
514502
{
515-
lock (State)
516-
lock (component)
517-
{
518-
State.ClearStateCache(component);
519-
State.SetModuleState(component, ParserState.Pending); // also clears module-exceptions
520-
}
503+
State.ClearStateCache(component);
504+
State.SetModuleState(component, ParserState.Pending); // also clears module-exceptions
521505

522506
var linkedTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_central.Token, token);
523507

@@ -566,11 +550,7 @@ private void ParseAsyncInternal(VBComponent component, CancellationToken token,
566550
var parser = new ComponentParseTask(component, preprocessor, _attributeParser, rewriter);
567551
parser.ParseFailure += (sender, e) =>
568552
{
569-
lock (State)
570-
lock (component)
571-
{
572-
State.SetModuleState(component, ParserState.Error, e.Cause as SyntaxErrorException);
573-
}
553+
State.SetModuleState(component, ParserState.Error, e.Cause as SyntaxErrorException);
574554
};
575555
parser.ParseCompleted += (sender, e) =>
576556
{
@@ -587,11 +567,8 @@ private void ParseAsyncInternal(VBComponent component, CancellationToken token,
587567
State.SetModuleState(component, ParserState.Parsed);
588568
}
589569
};
590-
lock (State)
591-
lock (component)
592-
{
593-
State.SetModuleState(component, ParserState.Parsing);
594-
}
570+
State.SetModuleState(component, ParserState.Parsing);
571+
595572
parser.Start(token);
596573
}
597574

@@ -611,10 +588,7 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
611588
{
612589
projectDeclaration = CreateProjectDeclaration(projectQualifiedName, project);
613590
_projectDeclarations.AddOrUpdate(projectQualifiedName.ProjectId, projectDeclaration, (s, c) => projectDeclaration);
614-
lock (State)
615-
{
616-
State.AddDeclaration(projectDeclaration);
617-
}
591+
State.AddDeclaration(projectDeclaration);
618592
}
619593
Logger.Debug("Creating declarations for module {0}.", qualifiedModuleName.Name);
620594
var declarationsListener = new DeclarationSymbolsListener(State, qualifiedModuleName, component.Type, State.GetModuleAnnotations(component), State.GetModuleAttributes(component), projectDeclaration);
@@ -627,10 +601,7 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
627601
catch (Exception exception)
628602
{
629603
Logger.Error(exception, "Exception thrown acquiring declarations for '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
630-
lock (State)
631-
{
632-
State.SetModuleState(component, ParserState.ResolverError);
633-
}
604+
State.SetModuleState(component, ParserState.ResolverError);
634605
}
635606
}
636607

0 commit comments

Comments
 (0)