Skip to content

Commit dfd7e56

Browse files
committed
Fix failing tests
1 parent 55968ab commit dfd7e56

File tree

2 files changed

+66
-76
lines changed

2 files changed

+66
-76
lines changed

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 65 additions & 75 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,6 @@ public class RubberduckParser : IRubberduckParser
3131
private readonly IDictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>> _componentAttributes
3232
= new Dictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>>();
3333

34-
3534
private readonly ReferencedDeclarationsCollector _comReflector;
3635

3736
private readonly VBE _vbe;
@@ -57,7 +56,6 @@ public RubberduckParser(
5756
state.ParseRequest += ReparseRequested;
5857
}
5958

60-
6159
private void ReparseRequested(object sender, ParseRequestEventArgs e)
6260
{
6361
if (e.IsFullReparseRequest)
@@ -72,10 +70,26 @@ private void ReparseRequested(object sender, ParseRequestEventArgs e)
7270
{
7371
ParseAsync(e.Component, CancellationToken.None).Wait();
7472

75-
if (_state.Status != ParserState.Error)
73+
if (_resolverTokenSource.IsCancellationRequested || _central.IsCancellationRequested)
7674
{
77-
Logger.Trace("Starting resolver task");
78-
Resolve(_central.Token);
75+
return;
76+
}
77+
78+
if (_state.Status == ParserState.Error) { return; }
79+
80+
var qualifiedName = new QualifiedModuleName(e.Component);
81+
Logger.Debug("Module '{0}' {1}", qualifiedName.ComponentName,
82+
_state.IsNewOrModified(qualifiedName) ? "was modified" : "was NOT modified");
83+
84+
_state.SetModuleState(e.Component, ParserState.Resolving);
85+
ResolveDeclarations(qualifiedName.Component,
86+
_state.ParseTrees.Find(s => s.Key == qualifiedName).Value);
87+
88+
_state.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
89+
90+
if (_state.Status < ParserState.Error)
91+
{
92+
ResolveReferencesAsync();
7993
}
8094
});
8195
}
@@ -103,6 +117,12 @@ public void Parse()
103117
}
104118
}
105119

120+
// tests do not fire events when components are removed--clear components
121+
foreach (var tree in _state.ParseTrees)
122+
{
123+
_state.ClearStateCache(tree.Key.Component);
124+
}
125+
106126
SyncComReferences(_state.Projects);
107127

108128
foreach (var component in components)
@@ -119,18 +139,42 @@ public void Parse()
119139
}
120140
}
121141

142+
_projectDeclarations.Clear();
143+
_state.ClearBuiltInReferences();
144+
122145
var parseTasks = new Task[components.Count];
123146
for (var i = 0; i < components.Count; i++)
124147
{
125-
parseTasks[i] = ParseAsync(components[i], CancellationToken.None);
148+
var index = i;
149+
parseTasks[i] = new Task(() =>
150+
{
151+
ParseAsync(components[index], CancellationToken.None).Wait();
152+
153+
if (_resolverTokenSource.IsCancellationRequested || _central.IsCancellationRequested)
154+
{
155+
return;
156+
}
157+
158+
if (_state.Status == ParserState.Error) { return; }
159+
160+
var qualifiedName = new QualifiedModuleName(components[index]);
161+
Logger.Debug("Module '{0}' {1}", qualifiedName.ComponentName,
162+
_state.IsNewOrModified(qualifiedName) ? "was modified" : "was NOT modified");
163+
164+
_state.SetModuleState(components[index], ParserState.Resolving);
165+
ResolveDeclarations(qualifiedName.Component,
166+
_state.ParseTrees.Find(s => s.Key == qualifiedName).Value);
167+
});
168+
169+
parseTasks[i].Start();
126170
}
127171

128172
Task.WaitAll(parseTasks);
173+
_state.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
129174

130-
if (_state.Status != ParserState.Error)
175+
if (_state.Status < ParserState.Error)
131176
{
132-
Logger.Trace("Starting resolver task");
133-
Resolve(_central.Token); // Tests expect this to be synchronous
177+
Task.WaitAll(ResolveReferencesAsync());
134178
}
135179
}
136180

@@ -241,7 +285,7 @@ private void ParseAll()
241285
}
242286
}
243287

244-
private void ResolveReferencesAsync()
288+
private Task[] ResolveReferencesAsync()
245289
{
246290
var finder = new DeclarationFinder(_state.AllDeclarations, _state.AllComments, _state.AllAnnotations);
247291
var passes = new List<ICompilationPass>
@@ -253,15 +297,20 @@ private void ResolveReferencesAsync()
253297
};
254298
passes.ForEach(p => p.Execute());
255299

256-
foreach (var kvp in _state.ParseTrees)
300+
var tasks = new Task[_state.ParseTrees.Count];
301+
302+
for (var index = 0; index < _state.ParseTrees.Count; index++)
257303
{
304+
var kvp = _state.ParseTrees[index];
258305
if (_resolverTokenSource.IsCancellationRequested || _central.IsCancellationRequested)
259306
{
260-
return;
307+
return new Task[0];
261308
}
262309

263-
Task.Run(() => ResolveReferences(finder, kvp.Key.Component, kvp.Value));
310+
tasks[index] = Task.Run(() => ResolveReferences(finder, kvp.Key.Component, kvp.Value));
264311
}
312+
313+
return tasks;
265314
}
266315

267316
private void AddBuiltInDeclarations(IReadOnlyList<VBProject> projects)
@@ -418,7 +467,7 @@ private void UnloadComReference(Reference reference, IReadOnlyList<VBProject> pr
418467
}
419468
}
420469

421-
public Task ParseAsync(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null)
470+
private Task ParseAsync(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null)
422471
{
423472
lock (_state)
424473
lock (component)
@@ -503,66 +552,7 @@ private void ParseAsyncInternal(VBComponent component, CancellationToken token,
503552
parser.Start(token);
504553
}
505554

506-
private void Resolve(CancellationToken token)
507-
{
508-
State.SetStatusAndFireStateChanged(ParserState.Resolving);
509-
var sharedTokenSource = CancellationTokenSource.CreateLinkedTokenSource(_resolverTokenSource.Token, token);
510-
// tests expect this to be synchronous :/
511-
//Task.Run(() => ResolveInternal(sharedTokenSource.Token));
512-
ResolveInternal(sharedTokenSource.Token);
513-
}
514-
515-
private void ResolveInternal(CancellationToken token)
516-
{
517-
var components = new List<VBComponent>();
518-
foreach (var project in _state.Projects)
519-
{
520-
if (project.Protection == vbext_ProjectProtection.vbext_pp_locked)
521-
{
522-
continue;
523-
}
524-
525-
foreach (VBComponent component in project.VBComponents)
526-
{
527-
components.Add(component);
528-
}
529-
}
530-
531-
if (!_state.HasAllParseTrees(components))
532-
{
533-
return;
534-
}
535-
_projectDeclarations.Clear();
536-
_state.ClearBuiltInReferences();
537-
foreach (var kvp in _state.ParseTrees)
538-
{
539-
var qualifiedName = kvp.Key;
540-
Logger.Debug("Module '{0}' {1}", qualifiedName.ComponentName, _state.IsNewOrModified(qualifiedName) ? "was modified" : "was NOT modified");
541-
// modified module; walk parse tree and re-acquire all declarations
542-
if (token.IsCancellationRequested) return;
543-
ResolveDeclarations(qualifiedName.Component, kvp.Value);
544-
}
545-
546-
_state.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
547-
548-
// walk all parse trees (modified or not) for identifier references
549-
var finder = new DeclarationFinder(_state.AllDeclarations, _state.AllComments, _state.AllAnnotations);
550-
var passes = new List<ICompilationPass>
551-
{
552-
// This pass has to come first because the type binding resolution depends on it.
553-
new ProjectReferencePass(finder),
554-
new TypeHierarchyPass(finder, new VBAExpressionParser()),
555-
new TypeAnnotationPass(finder, new VBAExpressionParser())
556-
};
557-
passes.ForEach(p => p.Execute());
558-
foreach (var kvp in _state.ParseTrees)
559-
{
560-
if (token.IsCancellationRequested) return;
561-
ResolveReferences(finder, kvp.Key.Component, kvp.Value);
562-
}
563-
}
564-
565-
private readonly Dictionary<string, Declaration> _projectDeclarations = new Dictionary<string, Declaration>();
555+
private readonly ConcurrentDictionary<string, Declaration> _projectDeclarations = new ConcurrentDictionary<string, Declaration>();
566556
private void ResolveDeclarations(VBComponent component, IParseTree tree)
567557
{
568558
if (component == null) { return; }
@@ -577,7 +567,7 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
577567
if (!_projectDeclarations.TryGetValue(projectQualifiedName.ProjectId, out projectDeclaration))
578568
{
579569
projectDeclaration = CreateProjectDeclaration(projectQualifiedName, project);
580-
_projectDeclarations.Add(projectQualifiedName.ProjectId, projectDeclaration);
570+
_projectDeclarations.AddOrUpdate(projectQualifiedName.ProjectId, projectDeclaration, (s, c) => projectDeclaration);
581571
lock (_state)
582572
{
583573
_state.AddDeclaration(projectDeclaration);

RubberduckTests/UnitTesting/ViewModelTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@ Public Sub TestMethod1()
4242
public void UIRemovesRemovedTestMethods()
4343
{
4444
var testMethods = @"'@TestMethod
45-
Public Sub TestMethod1()
45+
Public Sub TestMethod{0}()
4646
End Sub";
4747

4848
var builder = new MockVbeBuilder();

0 commit comments

Comments
 (0)