Skip to content

Commit d95999b

Browse files
committed
fixes #1311; problem reporting error state now
1 parent c99f1f2 commit d95999b

File tree

9 files changed

+149
-88
lines changed

9 files changed

+149
-88
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
}

RetailCoder.VBE/packages.config

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
<package id="Antlr4" version="4.3.0" targetFramework="net45" />
44
<package id="Antlr4.Runtime" version="4.3.0" targetFramework="net45" />
55
<package id="Castle.Core" version="3.2.0" targetFramework="net45" />
6-
<package id="EventHook" version="1.4.29" targetFramework="net45" />
6+
<package id="EventHook" version="1.4.34" targetFramework="net45" />
77
<package id="Ninject" version="3.2.2.0" targetFramework="net45" />
88
<package id="Ninject.Extensions.Conventions" version="3.2.0.0" targetFramework="net45" />
99
<package id="Ninject.Extensions.Factory" version="3.2.1.0" targetFramework="net45" />

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: 82 additions & 35 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,30 +117,77 @@ 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

143+
private static readonly ParserState[] States = Enum.GetValues(typeof(ParserState)).Cast<ParserState>().ToArray();
129144
private ParserState EvaluateParserState()
130145
{
131146
var moduleStates = _moduleStates.Values.ToList();
132147

133-
var prelim = moduleStates.Max();
134-
if (prelim == ParserState.Parsed && moduleStates.Any(s => s != ParserState.Parsed))
148+
var state = States.SingleOrDefault(value => moduleStates.All(ps => ps == value));
149+
if (state != default(ParserState))
150+
{
151+
// if all modules are in the same state, we have our result.
152+
Debug.WriteLine("ParserState evaluates to '{0}' (thread {1})", state, Thread.CurrentThread.ManagedThreadId);
153+
return state;
154+
}
155+
156+
// error state takes precedence over every other state
157+
if (moduleStates.Any(ms => ms == ParserState.Error))
158+
{
159+
Debug.WriteLine("ParserState evaluates to '{0}' (thread {1})", ParserState.Error, Thread.CurrentThread.ManagedThreadId);
160+
return ParserState.Error;
161+
}
162+
if (moduleStates.Any(ms => ms == ParserState.ResolverError))
163+
{
164+
Debug.WriteLine("ParserState evaluates to '{0}' (thread {1})", ParserState.ResolverError, Thread.CurrentThread.ManagedThreadId);
165+
return ParserState.ResolverError;
166+
}
167+
168+
// "working" states are toggled when *any* module has them.
169+
var result = moduleStates.Min();
170+
if (moduleStates.Any(ms => ms == ParserState.LoadingReference))
135171
{
136-
prelim = moduleStates.Where(s => s != ParserState.Parsed).Max();
172+
result = ParserState.LoadingReference;
137173
}
138-
return prelim;
174+
if (moduleStates.Any(ms => ms == ParserState.Parsing))
175+
{
176+
result = ParserState.Parsing;
177+
}
178+
if (moduleStates.Any(ms => ms == ParserState.Resolving))
179+
{
180+
result = ParserState.Resolving;
181+
}
182+
183+
// otherwise, return the
184+
Debug.WriteLine("ParserState evaluates to '{0}' (thread {1})", result, Thread.CurrentThread.ManagedThreadId);
185+
return result;
139186
}
140187

141188
public ParserState GetModuleState(VBComponent component)
142189
{
143-
return _moduleStates.GetOrAdd(component, ParserState.Pending);
190+
return _moduleStates.GetOrAdd(new QualifiedModuleName(component), ParserState.Pending);
144191
}
145192

146193
private ParserState _status;
@@ -182,7 +229,7 @@ public IEnumerable<QualifiedContext> ObsoleteLetContexts
182229

183230
internal void SetModuleAttributes(VBComponent component, IDictionary<Tuple<string, DeclarationType>, Attributes> attributes)
184231
{
185-
_moduleAttributes.AddOrUpdate(component, attributes, (c, s) => attributes);
232+
_moduleAttributes.AddOrUpdate(new QualifiedModuleName(component), attributes, (c, s) => attributes);
186233
}
187234

188235
private IEnumerable<QualifiedContext> _emptyStringLiterals = new List<QualifiedContext>();
@@ -214,7 +261,7 @@ public IEnumerable<CommentNode> AllComments
214261
public IEnumerable<CommentNode> GetModuleComments(VBComponent component)
215262
{
216263
IList<CommentNode> result;
217-
if (_comments.TryGetValue(component, out result))
264+
if (_comments.TryGetValue(new QualifiedModuleName(component), out result))
218265
{
219266
return result;
220267
}
@@ -224,7 +271,7 @@ public IEnumerable<CommentNode> GetModuleComments(VBComponent component)
224271

225272
public void SetModuleComments(VBComponent component, IEnumerable<CommentNode> comments)
226273
{
227-
_comments[component] = comments.ToList();
274+
_comments[new QualifiedModuleName(component)] = comments.ToList();
228275
}
229276

230277
/// <summary>
@@ -254,7 +301,7 @@ public IReadOnlyList<Declaration> AllUserDeclarations
254301

255302
internal IDictionary<Tuple<string, DeclarationType>, Attributes> getModuleAttributes(VBComponent vbComponent)
256303
{
257-
return _moduleAttributes[vbComponent];
304+
return _moduleAttributes[new QualifiedModuleName(vbComponent)];
258305
}
259306

260307
/// <summary>
@@ -319,19 +366,19 @@ public bool ClearDeclarations(VBComponent component)
319366
declarationsRemoved = declarations == null ? 0 : declarations.Count;
320367

321368
IParseTree tree;
322-
success = success && (!_parseTrees.ContainsKey(key.Component) || _parseTrees.TryRemove(key.Component, out tree));
369+
success = success && (!_parseTrees.ContainsKey(key) || _parseTrees.TryRemove(key, out tree));
323370

324371
ITokenStream stream;
325-
success = success && (!_tokenStreams.ContainsKey(key.Component) || _tokenStreams.TryRemove(key.Component, out stream));
372+
success = success && (!_tokenStreams.ContainsKey(key) || _tokenStreams.TryRemove(key, out stream));
326373

327374
ParserState state;
328-
success = success && (!_moduleStates.ContainsKey(key.Component) || _moduleStates.TryRemove(key.Component, out state));
375+
success = success && (!_moduleStates.ContainsKey(key) || _moduleStates.TryRemove(key, out state));
329376

330377
SyntaxErrorException exception;
331-
success = success && (!_moduleExceptions.ContainsKey(key.Component) || _moduleExceptions.TryRemove(key.Component, out exception));
378+
success = success && (!_moduleExceptions.ContainsKey(key) || _moduleExceptions.TryRemove(key, out exception));
332379

333380
IList<CommentNode> nodes;
334-
success = success && (!_comments.ContainsKey(key.Component) || _comments.TryRemove(key.Component, out nodes));
381+
success = success && (!_comments.ContainsKey(key) || _comments.TryRemove(key, out nodes));
335382
}
336383

337384
Debug.WriteLine("ClearDeclarations({0}): {1} - {2} declarations removed", component.Name, success ? "succeeded" : "failed", declarationsRemoved);
@@ -340,24 +387,24 @@ public bool ClearDeclarations(VBComponent component)
340387

341388
public void AddTokenStream(VBComponent component, ITokenStream stream)
342389
{
343-
_tokenStreams[component] = stream;
390+
_tokenStreams[new QualifiedModuleName(component)] = stream;
344391
}
345392

346393
public void AddParseTree(VBComponent component, IParseTree parseTree)
347394
{
348-
_parseTrees[component] = parseTree;
395+
_parseTrees[new QualifiedModuleName(component)] = parseTree;
349396
}
350397

351398
public IParseTree GetParseTree(VBComponent component)
352399
{
353-
return _parseTrees[component];
400+
return _parseTrees[new QualifiedModuleName(component)];
354401
}
355402

356-
public IEnumerable<KeyValuePair<VBComponent, IParseTree>> ParseTrees { get { return _parseTrees; } }
403+
public IEnumerable<KeyValuePair<QualifiedModuleName, IParseTree>> ParseTrees { get { return _parseTrees; } }
357404

358405
public TokenStreamRewriter GetRewriter(VBComponent component)
359406
{
360-
return new TokenStreamRewriter(_tokenStreams[component]);
407+
return new TokenStreamRewriter(_tokenStreams[new QualifiedModuleName(component)]);
361408
}
362409

363410
/// <summary>

0 commit comments

Comments
 (0)