Skip to content

Commit c630706

Browse files
committed
Merge pull request #1248 from retailcoder/next
closes #1246
2 parents f36e7d2 + 3dcde2f commit c630706

File tree

7 files changed

+122
-21
lines changed

7 files changed

+122
-21
lines changed

RetailCoder.VBE/App.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,7 @@ public App(VBE vbe, IMessageBox messageBox,
4747
IGeneralConfigService configService,
4848
IAppMenu appMenus,
4949
RubberduckCommandBar stateBar,
50-
IIndenter indenter/*,
50+
IIndenter indenter/*
5151
IRubberduckHooks hooks*/)
5252
{
5353
_vbe = vbe;

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -346,6 +346,8 @@
346346
<Compile Include="UI\About\AboutDialog.Designer.cs">
347347
<DependentUpon>AboutDialog.cs</DependentUpon>
348348
</Compile>
349+
<Compile Include="UI\Command\ShowParserErrorsCommand.cs" />
350+
<Compile Include="UI\Command\SyntaxErrorExtensions.cs" />
349351
<Compile Include="UI\Controls\DeclarationTypeToStringConverter.cs" />
350352
<Compile Include="UI\Controls\SearchResultPresenterInstanceManager.cs" />
351353
<Compile Include="UI\Controls\ISearchResultsWindowViewModel.cs" />

RetailCoder.VBE/UI/Command/MenuItems/RubberduckCommandBar.cs

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,18 +12,28 @@ public class RubberduckCommandBar
1212
{
1313
private readonly RubberduckParserState _state;
1414
private readonly VBE _vbe;
15+
private readonly IShowParserErrorsCommand _command;
1516

1617
private CommandBarButton _refreshButton;
1718
private CommandBarButton _statusButton;
1819

19-
public RubberduckCommandBar(RubberduckParserState state, VBE vbe)
20+
public RubberduckCommandBar(RubberduckParserState state, VBE vbe, IShowParserErrorsCommand command)
2021
{
2122
_state = state;
2223
_vbe = vbe;
24+
_command = command;
2325
_state.StateChanged += State_StateChanged;
2426
Initialize();
2527
}
2628

29+
private void _statusButton_Click(CommandBarButton Ctrl, ref bool CancelDefault)
30+
{
31+
if (_state.Status == ParserState.Error)
32+
{
33+
_command.Execute(null);
34+
}
35+
}
36+
2737
public void SetStatusText(string value = null)
2838
{
2939
_statusButton.Caption = value ?? RubberduckUI.ResourceManager.GetString("ParserState_" + _state.Status);
@@ -60,6 +70,7 @@ public void Initialize()
6070
_statusButton = (CommandBarButton)commandbar.Controls.Add(MsoControlType.msoControlButton);
6171
_statusButton.Style = MsoButtonStyle.msoButtonCaption;
6272
_statusButton.Tag = "Status";
73+
_statusButton.Click += _statusButton_Click;
6374

6475
commandbar.Visible = true;
6576
}
Lines changed: 69 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,69 @@
1+
using System;
2+
using System.Linq;
3+
using System.Runtime.InteropServices;
4+
using System.Windows.Input;
5+
using Microsoft.Vbe.Interop;
6+
using Rubberduck.Parsing.Symbols;
7+
using Rubberduck.Parsing.VBA;
8+
using Rubberduck.UI.Controls;
9+
10+
namespace Rubberduck.UI.Command
11+
{
12+
public interface IShowParserErrorsCommand : ICommand { }
13+
14+
[ComVisible(false)]
15+
public class ShowParserErrorsCommand : CommandBase, IShowParserErrorsCommand
16+
{
17+
private readonly INavigateCommand _navigateCommand;
18+
private readonly RubberduckParserState _state;
19+
private readonly ISearchResultsWindowViewModel _viewModel;
20+
private readonly SearchResultPresenterInstanceManager _presenterService;
21+
22+
public ShowParserErrorsCommand(INavigateCommand navigateCommand, RubberduckParserState state, ISearchResultsWindowViewModel viewModel, SearchResultPresenterInstanceManager presenterService)
23+
{
24+
_navigateCommand = navigateCommand;
25+
_state = state;
26+
_viewModel = viewModel;
27+
_presenterService = presenterService;
28+
}
29+
30+
public override void Execute(object parameter)
31+
{
32+
if (_state.Status != ParserState.Error)
33+
{
34+
return;
35+
}
36+
37+
var viewModel = CreateViewModel();
38+
_viewModel.AddTab(viewModel);
39+
_viewModel.SelectedTab = viewModel;
40+
41+
try
42+
{
43+
var presenter = _presenterService.Presenter(_viewModel);
44+
presenter.Show();
45+
}
46+
catch (Exception e)
47+
{
48+
Console.WriteLine(e);
49+
}
50+
}
51+
52+
private SearchResultsViewModel CreateViewModel()
53+
{
54+
var errors = from error in _state.ModuleExceptions
55+
let declaration = FindModuleDeclaration(error.Item1)
56+
select new SearchResultItem(declaration, error.Item2.GetNavigateCodeEventArgs(declaration), error.Item2.Message);
57+
58+
var viewModel = new SearchResultsViewModel(_navigateCommand, "Parser Errors", null, errors.ToList());
59+
return viewModel;
60+
}
61+
62+
private Declaration FindModuleDeclaration(VBComponent component)
63+
{
64+
return _state.AllUserDeclarations.Single(item => item.Project == component.Collection.Parent
65+
&& item.QualifiedName.QualifiedModuleName.Component == component
66+
&& (item.DeclarationType == DeclarationType.Class || item.DeclarationType == DeclarationType.Module));
67+
}
68+
}
69+
}
Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,14 @@
1+
using Rubberduck.Parsing.Symbols;
2+
using Rubberduck.VBEditor;
3+
4+
namespace Rubberduck.UI.Command
5+
{
6+
public static class SyntaxErrorExtensions
7+
{
8+
public static NavigateCodeEventArgs GetNavigateCodeEventArgs(this SyntaxErrorException exception, Declaration declaration)
9+
{
10+
var selection = new Selection(exception.LineNumber, exception.Position, exception.LineNumber, exception.Position);
11+
return new NavigateCodeEventArgs(declaration.QualifiedName.QualifiedModuleName, selection);
12+
}
13+
}
14+
}

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 19 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -191,8 +191,9 @@ public void ParseComponent(VBComponent vbComponent, TokenStreamRewriter rewriter
191191
commentListener
192192
};
193193

194-
var tree = GetParseTree(vbComponent, listeners, preprocessedModuleBody, qualifiedName);
195-
WalkParseTree(vbComponent, listeners, qualifiedName, tree);
194+
DeclarationSymbolsListener listener;
195+
var tree = GetParseTree(vbComponent, listeners, preprocessedModuleBody, qualifiedName, out listener);
196+
WalkParseTree(listeners, qualifiedName, tree, listener);
196197

197198
State.SetModuleState(vbComponent, ParserState.Parsed);
198199
}
@@ -212,12 +213,26 @@ public void ParseComponent(VBComponent vbComponent, TokenStreamRewriter rewriter
212213
}
213214
}
214215

215-
private IParseTree GetParseTree(VBComponent vbComponent, IParseTreeListener[] listeners, string code, QualifiedModuleName qualifiedName)
216+
private IParseTree GetParseTree(VBComponent vbComponent, IParseTreeListener[] listeners, string code, QualifiedModuleName qualifiedName, out DeclarationSymbolsListener declarationsListener)
216217
{
217218
var commentListener = listeners.OfType<CommentListener>().Single();
218219
ITokenStream stream;
219220

220221
var stopwatch = Stopwatch.StartNew();
222+
if (!_componentAttributes.ContainsKey(vbComponent))
223+
{
224+
_componentAttributes.Add(vbComponent, _attributeParser.Parse(vbComponent));
225+
}
226+
var attributes = _componentAttributes[vbComponent];
227+
228+
// cannot locate declarations in one pass *the way it's currently implemented*,
229+
// because the context in EnterSubStmt() doesn't *yet* have child nodes when the context enters.
230+
// so we need to EnterAmbiguousIdentifier() and evaluate the parent instead - this *might* work.
231+
declarationsListener = new DeclarationSymbolsListener(qualifiedName, Accessibility.Implicit, vbComponent.Type, _state.GetModuleComments(vbComponent), attributes);
232+
233+
declarationsListener.NewDeclaration += declarationsListener_NewDeclaration;
234+
declarationsListener.CreateModuleDeclarations();
235+
221236
var tree = ParseInternal(code, listeners, out stream);
222237
stopwatch.Stop();
223238
if (tree != null)
@@ -237,30 +252,15 @@ private IParseTree GetParseTree(VBComponent vbComponent, IParseTreeListener[] li
237252
private readonly IDictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>> _componentAttributes
238253
= new Dictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>>();
239254

240-
private void WalkParseTree(VBComponent vbComponent, IReadOnlyList<IParseTreeListener> listeners, QualifiedModuleName qualifiedName, IParseTree tree)
255+
private void WalkParseTree(IReadOnlyList<IParseTreeListener> listeners, QualifiedModuleName qualifiedName, IParseTree tree, DeclarationSymbolsListener declarationsListener)
241256
{
242257
var obsoleteCallsListener = listeners.OfType<ObsoleteCallStatementListener>().Single();
243258
var obsoleteLetListener = listeners.OfType<ObsoleteLetStatementListener>().Single();
244259
var emptyStringLiteralListener = listeners.OfType<EmptyStringLiteralListener>().Single();
245260
var argListsWithOneByRefParamListener = listeners.OfType<ArgListWithOneByRefParamListener>().Single();
246261

247-
if (!_componentAttributes.ContainsKey(vbComponent))
248-
{
249-
_componentAttributes.Add(vbComponent, _attributeParser.Parse(vbComponent));
250-
}
251-
var attributes = _componentAttributes[vbComponent];
252-
253-
// cannot locate declarations in one pass *the way it's currently implemented*,
254-
// because the context in EnterSubStmt() doesn't *yet* have child nodes when the context enters.
255-
// so we need to EnterAmbiguousIdentifier() and evaluate the parent instead - this *might* work.
256-
var declarationsListener = new DeclarationSymbolsListener(qualifiedName, Accessibility.Implicit, vbComponent.Type, _state.GetModuleComments(vbComponent), attributes);
257-
258-
declarationsListener.NewDeclaration += declarationsListener_NewDeclaration;
259-
declarationsListener.CreateModuleDeclarations();
260-
261262
var walker = new ParseTreeWalker();
262263
walker.Walk(declarationsListener, tree);
263-
declarationsListener.NewDeclaration -= declarationsListener_NewDeclaration;
264264

265265
_state.ObsoleteCallContexts = obsoleteCallsListener.Contexts.Select(context => new QualifiedContext(qualifiedName, context));
266266
_state.ObsoleteLetContexts = obsoleteLetListener.Contexts.Select(context => new QualifiedContext(qualifiedName, context));

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,11 @@ private void OnStateChanged()
6969
private readonly ConcurrentDictionary<VBComponent, SyntaxErrorException> _moduleExceptions =
7070
new ConcurrentDictionary<VBComponent, SyntaxErrorException>();
7171

72+
public IReadOnlyList<Tuple<VBComponent, SyntaxErrorException>> ModuleExceptions
73+
{
74+
get { return _moduleExceptions.Select(kvp => Tuple.Create(kvp.Key, kvp.Value)).Where(item => item.Item2 != null).ToList(); }
75+
}
76+
7277
public event EventHandler<ParseProgressEventArgs> ModuleStateChanged;
7378

7479
private void OnModuleStateChanged(VBComponent component, ParserState state)

0 commit comments

Comments
 (0)