Skip to content

Commit 4749ed0

Browse files
committed
revert RubberduckParserState.EvaluateParserState to a version that makes tests pass.... thing is, there's still a bug in that method..
2 parents 944d75b + 4f724da commit 4749ed0

File tree

9 files changed

+128
-126
lines changed

9 files changed

+128
-126
lines changed

RetailCoder.VBE/UI/Command/ShowParserErrorsCommand.cs

Lines changed: 16 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
using System;
2+
using System.Collections.Generic;
23
using System.Linq;
34
using System.Runtime.InteropServices;
45
using System.Windows.Input;
@@ -37,6 +38,11 @@ public override void Execute(object parameter)
3738
}
3839

3940
var viewModel = CreateViewModel();
41+
if (_viewModel == null)
42+
{
43+
return;
44+
}
45+
4046
_viewModel.AddTab(viewModel);
4147
_viewModel.SelectedTab = viewModel;
4248

@@ -55,22 +61,27 @@ private SearchResultsViewModel CreateViewModel()
5561
{
5662
var errors = from error in _state.ModuleExceptions
5763
let declaration = FindModuleDeclaration(error.Item1)
64+
where declaration != null
5865
select new SearchResultItem(declaration, error.Item2.GetNavigateCodeEventArgs(declaration), error.Item2.Message);
5966

60-
var viewModel = new SearchResultsViewModel(_navigateCommand, "Parser Errors", null, errors.ToList());
67+
var searchResultItems = errors as IList<SearchResultItem> ?? errors.ToList();
68+
var viewModel = new SearchResultsViewModel(_navigateCommand, "Parser Errors", null, searchResultItems);
6169
return viewModel;
6270
}
6371

6472
private Declaration FindModuleDeclaration(VBComponent component)
6573
{
74+
var projectName = component.ProjectName();
75+
76+
var project = _state.AllUserDeclarations.SingleOrDefault(item =>
77+
item.DeclarationType == DeclarationType.Project && item.ProjectName == projectName);
6678

6779
var result = _state.AllUserDeclarations.SingleOrDefault(item => item.ProjectName == component.Collection.Parent.ProjectName()
6880
&& item.QualifiedName.QualifiedModuleName.ComponentName == component.Name
6981
&& (item.DeclarationType == DeclarationType.Class || item.DeclarationType == DeclarationType.Module));
70-
return result
71-
?? // module isn't in parser state - give it a dummy declaration, just so the ViewModel has something to chew on:
72-
new Declaration(new QualifiedMemberName(new QualifiedModuleName(component), component.Name), null,
73-
null, component.Name, false, false, Accessibility.Global, DeclarationType.Module, false);
82+
83+
var declaration = new Declaration(new QualifiedMemberName(new QualifiedModuleName(component), component.Name), project, project.Scope, component.Name, false, false, Accessibility.Global, DeclarationType.Module, false);
84+
return result ?? declaration; // module isn't in parser state - give it a dummy declaration, just so the ViewModel has something to chew on
7485
}
7586
}
7687
}

RetailCoder.VBE/UI/Command/SyntaxErrorExtensions.cs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,8 @@ public static class SyntaxErrorExtensions
77
{
88
public static NavigateCodeEventArgs GetNavigateCodeEventArgs(this SyntaxErrorException exception, Declaration declaration)
99
{
10+
if (declaration == null) return null;
11+
1012
var selection = new Selection(exception.LineNumber, exception.Position, exception.LineNumber, exception.Position);
1113
return new NavigateCodeEventArgs(declaration.QualifiedName.QualifiedModuleName, selection);
1214
}

RetailCoder.VBE/UnitTesting/NewUnitTestModuleCommand.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ public static void NewUnitTestModule(VBE vbe)
5151
hasOptionExplicit = module.CodeModule.Lines[1, module.CodeModule.CountOfDeclarationLines].Contains("Option Explicit");
5252
}
5353

54-
var options = String.Concat(hasOptionExplicit ? String.Empty : "Option Explicit\n", "Option Private Module\n\n");
54+
var options = string.Concat(hasOptionExplicit ? string.Empty : "Option Explicit\n", "Option Private Module\n\n");
5555

5656
module.CodeModule.AddFromString(options + TestModuleEmptyTemplate);
5757
module.Activate();
@@ -67,7 +67,7 @@ private static string GetNextTestModuleName(VBProject project)
6767
var names = project.ComponentNames();
6868
var index = names.Count(n => n.StartsWith(TestModuleBaseName)) + 1;
6969

70-
return String.Concat(TestModuleBaseName, index);
70+
return string.Concat(TestModuleBaseName, index);
7171
}
7272
}
7373
}

Rubberduck.Parsing/VBA/ParserState.cs

Lines changed: 9 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,38 +1,39 @@
11
namespace Rubberduck.Parsing.VBA
22
{
3+
//note: ordering of the members is important
34
public enum ParserState
45
{
56
/// <summary>
67
/// Parse was requested but hasn't started yet.
78
/// </summary>
8-
Pending = 0,
9+
Pending,
910
/// <summary>
1011
/// Project references are being loaded into parser state.
1112
/// </summary>
12-
LoadingReference = 1,
13+
LoadingReference,
1314
/// <summary>
1415
/// Code from modified modules is being parsed.
1516
/// </summary>
16-
Parsing = 2,
17+
Parsing,
1718
/// <summary>
1819
/// Parse tree is waiting to be walked for identifier resolution.
1920
/// </summary>
20-
Parsed = 3,
21+
Parsed,
2122
/// <summary>
2223
/// Resolving identifier references.
2324
/// </summary>
24-
Resolving = 4,
25+
Resolving,
2526
/// <summary>
2627
/// Parser state is in sync with the actual code in the VBE.
2728
/// </summary>
28-
Ready = 5,
29+
Ready,
2930
/// <summary>
3031
/// Parsing could not be completed for one or more modules.
3132
/// </summary>
32-
Error = 99,
33+
Error,
3334
/// <summary>
3435
/// Parsing completed, but identifier references could not be resolved for one or more modules.
3536
/// </summary>
36-
ResolverError = 6,
37+
ResolverError,
3738
}
3839
}

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -274,13 +274,13 @@ private void ResolveInternal(CancellationToken token)
274274
foreach (var kvp in _state.ParseTrees)
275275
{
276276
if (token.IsCancellationRequested) return;
277-
ResolveDeclarations(kvp.Key, kvp.Value);
277+
ResolveDeclarations(kvp.Key.Component, kvp.Value);
278278
}
279279
var finder = new DeclarationFinder(_state.AllDeclarations, _state.AllComments);
280280
foreach (var kvp in _state.ParseTrees)
281281
{
282282
if (token.IsCancellationRequested) return;
283-
ResolveReferences(finder, kvp.Key, kvp.Value);
283+
ResolveReferences(finder, kvp.Key.Component, kvp.Value);
284284
}
285285
}
286286

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 48 additions & 73 deletions
Original file line numberDiff line numberDiff line change
@@ -50,23 +50,23 @@ public sealed class RubberduckParserState
5050
private readonly ConcurrentDictionary<QualifiedModuleName, ConcurrentDictionary<Declaration, byte>> _declarations =
5151
new ConcurrentDictionary<QualifiedModuleName, ConcurrentDictionary<Declaration, byte>>();
5252

53-
private readonly ConcurrentDictionary<VBComponent, ITokenStream> _tokenStreams =
54-
new ConcurrentDictionary<VBComponent, ITokenStream>();
53+
private readonly ConcurrentDictionary<QualifiedModuleName, ITokenStream> _tokenStreams =
54+
new ConcurrentDictionary<QualifiedModuleName, ITokenStream>();
5555

56-
private readonly ConcurrentDictionary<VBComponent, IParseTree> _parseTrees =
57-
new ConcurrentDictionary<VBComponent, IParseTree>();
56+
private readonly ConcurrentDictionary<QualifiedModuleName, IParseTree> _parseTrees =
57+
new ConcurrentDictionary<QualifiedModuleName, IParseTree>();
5858

59-
private readonly ConcurrentDictionary<VBComponent, ParserState> _moduleStates =
60-
new ConcurrentDictionary<VBComponent, ParserState>();
59+
private readonly ConcurrentDictionary<QualifiedModuleName, ParserState> _moduleStates =
60+
new ConcurrentDictionary<QualifiedModuleName, ParserState>();
6161

62-
private readonly ConcurrentDictionary<VBComponent, IList<CommentNode>> _comments =
63-
new ConcurrentDictionary<VBComponent, IList<CommentNode>>();
62+
private readonly ConcurrentDictionary<QualifiedModuleName, IList<CommentNode>> _comments =
63+
new ConcurrentDictionary<QualifiedModuleName, IList<CommentNode>>();
6464

65-
private readonly ConcurrentDictionary<VBComponent, SyntaxErrorException> _moduleExceptions =
66-
new ConcurrentDictionary<VBComponent, SyntaxErrorException>();
65+
private readonly ConcurrentDictionary<QualifiedModuleName, SyntaxErrorException> _moduleExceptions =
66+
new ConcurrentDictionary<QualifiedModuleName, SyntaxErrorException>();
6767

68-
private readonly ConcurrentDictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>> _moduleAttributes =
69-
new ConcurrentDictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>>();
68+
private readonly ConcurrentDictionary<QualifiedModuleName, IDictionary<Tuple<string, DeclarationType>, Attributes>> _moduleAttributes =
69+
new ConcurrentDictionary<QualifiedModuleName, IDictionary<Tuple<string, DeclarationType>, Attributes>>();
7070

7171
public void AddProject(VBProject project)
7272
{
@@ -90,7 +90,7 @@ public void RemoveProject(VBProject project)
9090

9191
public IReadOnlyList<Tuple<VBComponent, SyntaxErrorException>> ModuleExceptions
9292
{
93-
get { return _moduleExceptions.Select(kvp => Tuple.Create(kvp.Key, kvp.Value)).Where(item => item.Item2 != null).ToList(); }
93+
get { return _moduleExceptions.Select(kvp => Tuple.Create(kvp.Key.Component, kvp.Value)).Where(item => item.Item2 != null).ToList(); }
9494
}
9595

9696
public event EventHandler<ParserStateEventArgs> StateChanged;
@@ -117,70 +117,45 @@ private void OnModuleStateChanged(VBComponent component, ParserState state)
117117

118118
public void SetModuleState(VBComponent component, ParserState state, SyntaxErrorException parserError = null)
119119
{
120-
_moduleStates.AddOrUpdate(component, state, (c, s) => state);
121-
_moduleExceptions.AddOrUpdate(component, parserError, (c, e) => parserError);
120+
if (AllUserDeclarations.Any())
121+
{
122+
var projectName = component.ProjectName();
123+
var project = AllUserDeclarations.SingleOrDefault(item =>
124+
item.DeclarationType == DeclarationType.Project && item.ProjectName == projectName);
125+
126+
if (project == null)
127+
{
128+
// ghost component shouldn't even exist
129+
ClearDeclarations(component);
130+
return;
131+
}
132+
}
133+
var key = new QualifiedModuleName(component);
134+
_moduleStates.AddOrUpdate(key, state, (c, s) => state);
135+
_moduleExceptions.AddOrUpdate(key, parserError, (c, e) => parserError);
122136

123-
Debug.WriteLine("Module '{0}' state is changing to '{1}' (thread {2})", component.Name, state, Thread.CurrentThread.ManagedThreadId);
137+
Debug.WriteLine("Module '{0}' state is changing to '{1}' (thread {2})", key.ComponentName, state, Thread.CurrentThread.ManagedThreadId);
124138
OnModuleStateChanged(component, state);
125139

126140
Status = EvaluateParserState();
127141
}
128142

129-
private static readonly ParserState[] States = Enum.GetValues(typeof(ParserState)).Cast<ParserState>().ToArray();
143+
//private static readonly ParserState[] States = Enum.GetValues(typeof(ParserState)).Cast<ParserState>().ToArray();
130144
private ParserState EvaluateParserState()
131145
{
132146
var moduleStates = _moduleStates.Values.ToList();
133147

134148
var prelim = moduleStates.Max();
135149
if (prelim == ParserState.Parsed && moduleStates.Any(s => s != ParserState.Parsed))
136150
{
137-
prelim = moduleStates.Where(s => s < ParserState.Parsed).Max();
151+
prelim = moduleStates.Where(s => s != ParserState.Parsed).Max();
138152
}
139153
return prelim;
140-
//var moduleStates = _moduleStates.Values.ToList();
141-
142-
//var state = States.SingleOrDefault(value => moduleStates.All(ps => ps == value));
143-
//if (state != default(ParserState))
144-
//{
145-
// // if all modules are in the same state, we have our result.
146-
// Debug.WriteLine("ParserState evaluates to '{0}' (thread {1})", state, Thread.CurrentThread.ManagedThreadId);
147-
// return state;
148-
//}
149-
150-
//// error state takes precedence over every other state
151-
//if (moduleStates.Any(ms => ms == ParserState.Error))
152-
//{
153-
// Debug.WriteLine("ParserState evaluates to '{0}' (thread {1})", ParserState.Error, Thread.CurrentThread.ManagedThreadId);
154-
// return ParserState.Error;
155-
//}
156-
//if (moduleStates.Any(ms => ms == ParserState.ResolverError))
157-
//{
158-
// Debug.WriteLine("ParserState evaluates to '{0}' (thread {1})", ParserState.ResolverError, Thread.CurrentThread.ManagedThreadId);
159-
// return ParserState.ResolverError;
160-
//}
161-
162-
//// "working" states are toggled when *any* module has them.
163-
//var result = moduleStates.Min();
164-
//if (moduleStates.Any(ms => ms == ParserState.LoadingReference))
165-
//{
166-
// result = ParserState.LoadingReference;
167-
//}
168-
//if (moduleStates.Any(ms => ms == ParserState.Parsing))
169-
//{
170-
// result = ParserState.Parsing;
171-
//}
172-
//if (moduleStates.Any(ms => ms == ParserState.Resolving))
173-
//{
174-
// result = ParserState.Resolving;
175-
//}
176-
177-
//// otherwise, return the
178-
//Debug.WriteLine("ParserState evaluates to '{0}' (thread {1})", result, Thread.CurrentThread.ManagedThreadId);
179-
//return result;
180154
}
155+
181156
public ParserState GetModuleState(VBComponent component)
182157
{
183-
return _moduleStates.GetOrAdd(component, ParserState.Pending);
158+
return _moduleStates.GetOrAdd(new QualifiedModuleName(component), ParserState.Pending);
184159
}
185160

186161
private ParserState _status;
@@ -222,7 +197,7 @@ public IEnumerable<QualifiedContext> ObsoleteLetContexts
222197

223198
internal void SetModuleAttributes(VBComponent component, IDictionary<Tuple<string, DeclarationType>, Attributes> attributes)
224199
{
225-
_moduleAttributes.AddOrUpdate(component, attributes, (c, s) => attributes);
200+
_moduleAttributes.AddOrUpdate(new QualifiedModuleName(component), attributes, (c, s) => attributes);
226201
}
227202

228203
private IEnumerable<QualifiedContext> _emptyStringLiterals = new List<QualifiedContext>();
@@ -254,7 +229,7 @@ public IEnumerable<CommentNode> AllComments
254229
public IEnumerable<CommentNode> GetModuleComments(VBComponent component)
255230
{
256231
IList<CommentNode> result;
257-
if (_comments.TryGetValue(component, out result))
232+
if (_comments.TryGetValue(new QualifiedModuleName(component), out result))
258233
{
259234
return result;
260235
}
@@ -264,7 +239,7 @@ public IEnumerable<CommentNode> GetModuleComments(VBComponent component)
264239

265240
public void SetModuleComments(VBComponent component, IEnumerable<CommentNode> comments)
266241
{
267-
_comments[component] = comments.ToList();
242+
_comments[new QualifiedModuleName(component)] = comments.ToList();
268243
}
269244

270245
/// <summary>
@@ -294,7 +269,7 @@ public IReadOnlyList<Declaration> AllUserDeclarations
294269

295270
internal IDictionary<Tuple<string, DeclarationType>, Attributes> getModuleAttributes(VBComponent vbComponent)
296271
{
297-
return _moduleAttributes[vbComponent];
272+
return _moduleAttributes[new QualifiedModuleName(vbComponent)];
298273
}
299274

300275
/// <summary>
@@ -359,19 +334,19 @@ public bool ClearDeclarations(VBComponent component)
359334
declarationsRemoved = declarations == null ? 0 : declarations.Count;
360335

361336
IParseTree tree;
362-
success = success && (!_parseTrees.ContainsKey(key.Component) || _parseTrees.TryRemove(key.Component, out tree));
337+
success = success && (!_parseTrees.ContainsKey(key) || _parseTrees.TryRemove(key, out tree));
363338

364339
ITokenStream stream;
365-
success = success && (!_tokenStreams.ContainsKey(key.Component) || _tokenStreams.TryRemove(key.Component, out stream));
340+
success = success && (!_tokenStreams.ContainsKey(key) || _tokenStreams.TryRemove(key, out stream));
366341

367342
ParserState state;
368-
success = success && (!_moduleStates.ContainsKey(key.Component) || _moduleStates.TryRemove(key.Component, out state));
343+
success = success && (!_moduleStates.ContainsKey(key) || _moduleStates.TryRemove(key, out state));
369344

370345
SyntaxErrorException exception;
371-
success = success && (!_moduleExceptions.ContainsKey(key.Component) || _moduleExceptions.TryRemove(key.Component, out exception));
346+
success = success && (!_moduleExceptions.ContainsKey(key) || _moduleExceptions.TryRemove(key, out exception));
372347

373348
IList<CommentNode> nodes;
374-
success = success && (!_comments.ContainsKey(key.Component) || _comments.TryRemove(key.Component, out nodes));
349+
success = success && (!_comments.ContainsKey(key) || _comments.TryRemove(key, out nodes));
375350
}
376351

377352
Debug.WriteLine("ClearDeclarations({0}): {1} - {2} declarations removed", component.Name, success ? "succeeded" : "failed", declarationsRemoved);
@@ -380,24 +355,24 @@ public bool ClearDeclarations(VBComponent component)
380355

381356
public void AddTokenStream(VBComponent component, ITokenStream stream)
382357
{
383-
_tokenStreams[component] = stream;
358+
_tokenStreams[new QualifiedModuleName(component)] = stream;
384359
}
385360

386361
public void AddParseTree(VBComponent component, IParseTree parseTree)
387362
{
388-
_parseTrees[component] = parseTree;
363+
_parseTrees[new QualifiedModuleName(component)] = parseTree;
389364
}
390365

391366
public IParseTree GetParseTree(VBComponent component)
392367
{
393-
return _parseTrees[component];
368+
return _parseTrees[new QualifiedModuleName(component)];
394369
}
395370

396-
public IEnumerable<KeyValuePair<VBComponent, IParseTree>> ParseTrees { get { return _parseTrees; } }
371+
public IEnumerable<KeyValuePair<QualifiedModuleName, IParseTree>> ParseTrees { get { return _parseTrees; } }
397372

398373
public TokenStreamRewriter GetRewriter(VBComponent component)
399374
{
400-
return new TokenStreamRewriter(_tokenStreams[component]);
375+
return new TokenStreamRewriter(_tokenStreams[new QualifiedModuleName(component)]);
401376
}
402377

403378
/// <summary>

0 commit comments

Comments
 (0)