Skip to content

Commit 62e6783

Browse files
authored
Merge pull request #2746 from comintern/next
Delegated selection event handling responsibilities out of App.cs.
2 parents 127ad15 + 76cf060 commit 62e6783

File tree

10 files changed

+320
-194
lines changed

10 files changed

+320
-194
lines changed

RetailCoder.VBE/App.cs

Lines changed: 3 additions & 175 deletions
Original file line numberDiff line numberDiff line change
@@ -3,33 +3,23 @@
33
using Infralution.Localization.Wpf;
44
using NLog;
55
using Rubberduck.Common;
6-
using Rubberduck.Parsing;
7-
using Rubberduck.Parsing.Symbols;
8-
using Rubberduck.Parsing.VBA;
96
using Rubberduck.Settings;
107
using Rubberduck.UI;
118
using Rubberduck.UI.Command.MenuItems;
129
using System;
1310
using System.Globalization;
14-
using System.Linq;
1511
using System.Windows.Forms;
1612
using Rubberduck.UI.Command;
1713
using Rubberduck.UI.Command.MenuItems.CommandBars;
18-
using Rubberduck.VBEditor.Events;
19-
using Rubberduck.VBEditor.SafeComWrappers;
2014
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
21-
using Rubberduck.VBEditor.SafeComWrappers.MSForms;
22-
using Rubberduck.VBEditor.SafeComWrappers.Office.Core.Abstract;
2315
using Rubberduck.VersionCheck;
2416
using Application = System.Windows.Forms.Application;
2517

2618
namespace Rubberduck
2719
{
2820
public sealed class App : IDisposable
2921
{
30-
private readonly IVBE _vbe;
3122
private readonly IMessageBox _messageBox;
32-
private readonly IParseCoordinator _parser;
3323
private readonly AutoSave.AutoSave _autoSave;
3424
private readonly IGeneralConfigService _configService;
3525
private readonly IAppMenu _appMenus;
@@ -44,171 +34,27 @@ public sealed class App : IDisposable
4434

4535
public App(IVBE vbe,
4636
IMessageBox messageBox,
47-
IParseCoordinator parser,
4837
IGeneralConfigService configService,
4938
IAppMenu appMenus,
5039
RubberduckCommandBar stateBar,
5140
IRubberduckHooks hooks,
5241
IVersionCheck version,
5342
CommandBase checkVersionCommand)
5443
{
55-
_vbe = vbe;
5644
_messageBox = messageBox;
57-
_parser = parser;
5845
_configService = configService;
59-
_autoSave = new AutoSave.AutoSave(_vbe, _configService);
46+
_autoSave = new AutoSave.AutoSave(vbe, _configService);
6047
_appMenus = appMenus;
6148
_stateBar = stateBar;
6249
_hooks = hooks;
6350
_version = version;
6451
_checkVersionCommand = checkVersionCommand;
6552

66-
VBENativeServices.SelectionChanged += _vbe_SelectionChanged;
67-
VBENativeServices.WindowFocusChange += _vbe_FocusChanged;
68-
6953
_configService.SettingsChanged += _configService_SettingsChanged;
70-
_parser.State.StateChanged += Parser_StateChanged;
71-
_parser.State.StatusMessageUpdate += State_StatusMessageUpdate;
72-
54+
7355
UiDispatcher.Initialize();
7456
}
7557

76-
//TODO - This should be able to move to the appropriate handling classes now.
77-
#region Statusbar
78-
79-
private void State_StatusMessageUpdate(object sender, RubberduckStatusMessageEventArgs e)
80-
{
81-
var message = e.Message;
82-
if (message == ParserState.LoadingReference.ToString())
83-
{
84-
// note: ugly hack to enable Rubberduck.Parsing assembly to do this
85-
message = RubberduckUI.ParserState_LoadingReference;
86-
}
87-
88-
_stateBar.SetStatusLabelCaption(message, _parser.State.ModuleExceptions.Count);
89-
}
90-
91-
private void _vbe_SelectionChanged(object sender, SelectionChangedEventArgs e)
92-
{
93-
RefreshSelection(e.CodePane);
94-
}
95-
96-
private void _vbe_FocusChanged(object sender, WindowChangedEventArgs e)
97-
{
98-
if (e.EventType == FocusType.GotFocus)
99-
{
100-
switch (e.Window.Type)
101-
{
102-
case WindowKind.Designer:
103-
//Designer or control on designer form selected.
104-
RefreshSelection(e.Window);
105-
break;
106-
case WindowKind.CodeWindow:
107-
//Caret changed in a code pane.
108-
RefreshSelection(e.CodePane);
109-
break;
110-
}
111-
}
112-
else if (e.EventType == FocusType.ChildFocus)
113-
{
114-
//Treeview selection changed in project window.
115-
RefreshSelection();
116-
}
117-
}
118-
119-
private ParserState _lastStatus;
120-
private Declaration _lastSelectedDeclaration;
121-
private void RefreshSelection(ICodePane pane)
122-
{
123-
if (pane == null || pane.IsWrappingNullReference)
124-
{
125-
return;
126-
}
127-
128-
var selectedDeclaration = _parser.State.FindSelectedDeclaration(pane);
129-
var caption = _stateBar.GetContextSelectionCaption(_vbe.ActiveCodePane, selectedDeclaration);
130-
UpdateStatusbarAndCommandState(caption, selectedDeclaration);
131-
}
132-
133-
private void RefreshSelection(IWindow window)
134-
{
135-
if (window == null || window.IsWrappingNullReference || window.Type != WindowKind.Designer)
136-
{
137-
return;
138-
}
139-
140-
var component = _vbe.SelectedVBComponent;
141-
var caption = GetComponentControlsCaption(component);
142-
//TODO: Need to find the selected declaration for the Form\Control.
143-
UpdateStatusbarAndCommandState(caption, null);
144-
}
145-
146-
private void RefreshSelection()
147-
{
148-
var caption = string.Empty;
149-
var component = _vbe.SelectedVBComponent;
150-
if (component == null || component.IsWrappingNullReference)
151-
{
152-
//The user might have selected the project node in Project Explorer
153-
//If they've chosen a folder, we'll return the project anyway
154-
caption = !_vbe.ActiveVBProject.IsWrappingNullReference
155-
? _vbe.ActiveVBProject.Name
156-
: null;
157-
}
158-
else
159-
{
160-
caption = component.Type == ComponentType.UserForm && component.HasOpenDesigner
161-
? GetComponentControlsCaption(component)
162-
: string.Format("{0}.{1} ({2})", component.ParentProject.Name, component.Name, component.Type);
163-
}
164-
//TODO: Need to find the selected declaration for the selected treeview item.
165-
UpdateStatusbarAndCommandState(caption, null);
166-
}
167-
168-
private void UpdateStatusbarAndCommandState(string caption, Declaration selectedDeclaration)
169-
{
170-
var refCount = selectedDeclaration == null ? 0 : selectedDeclaration.References.Count();
171-
_stateBar.SetContextSelectionCaption(caption, refCount);
172-
173-
var currentStatus = _parser.State.Status;
174-
if (ShouldEvaluateCanExecute(selectedDeclaration, currentStatus))
175-
{
176-
_appMenus.EvaluateCanExecute(_parser.State);
177-
_stateBar.EvaluateCanExecute(_parser.State);
178-
}
179-
180-
_lastStatus = currentStatus;
181-
_lastSelectedDeclaration = selectedDeclaration;
182-
}
183-
184-
private string GetComponentControlsCaption(IVBComponent component)
185-
{
186-
switch (component.SelectedControls.Count)
187-
{
188-
case 0:
189-
//TODO get the real designer for VB6
190-
return String.Format("{0}.{1} ({2})", component.ParentProject.Name, component.Name, "MSForms.UserForm");
191-
break;
192-
case 1:
193-
//TODO return the libraryName.className of the control
194-
IControl control = component.SelectedControls.First();
195-
return String.Format("{0}.{1}.{2} ({3})", component.ParentProject.Name, component.Name, control.Name, control.TypeName());
196-
break;
197-
default:
198-
return String.Format("{0}.{1} ({2})", component.ParentProject.Name, component.Name, RubberduckUI.ContextMultipleControlsSelection);
199-
break;
200-
}
201-
}
202-
203-
private bool ShouldEvaluateCanExecute(Declaration selectedDeclaration, ParserState currentStatus)
204-
{
205-
return _lastStatus != currentStatus ||
206-
(selectedDeclaration != null && !selectedDeclaration.Equals(_lastSelectedDeclaration)) ||
207-
(selectedDeclaration == null && _lastSelectedDeclaration != null);
208-
}
209-
210-
#endregion
211-
21258
private void _configService_SettingsChanged(object sender, ConfigurationChangedEventArgs e)
21359
{
21460
_config = _configService.LoadConfiguration();
@@ -254,8 +100,7 @@ public void Startup()
254100
_stateBar.Initialize();
255101
_hooks.HookHotkeys(); // need to hook hotkeys before we localize menus, to correctly display ShortcutTexts
256102
_appMenus.Localize();
257-
_stateBar.SetStatusLabelCaption(ParserState.Pending);
258-
_stateBar.EvaluateCanExecute(_parser.State);
103+
259104
UpdateLoggingLevel();
260105

261106
if (_config.UserSettings.GeneralSettings.CheckVersion)
@@ -276,14 +121,6 @@ public void Shutdown()
276121
}
277122
}
278123

279-
private void Parser_StateChanged(object sender, EventArgs e)
280-
{
281-
Logger.Debug("App handles StateChanged ({0}), evaluating menu states...", _parser.State.Status);
282-
_appMenus.EvaluateCanExecute(_parser.State);
283-
_stateBar.EvaluateCanExecute(_parser.State);
284-
_stateBar.SetStatusLabelCaption(_parser.State.Status, _parser.State.ModuleExceptions.Count);
285-
}
286-
287124
private void LoadConfig()
288125
{
289126
_config = _configService.LoadConfiguration();
@@ -354,15 +191,6 @@ public void Dispose()
354191
return;
355192
}
356193

357-
if (_parser != null && _parser.State != null)
358-
{
359-
_parser.State.StateChanged -= Parser_StateChanged;
360-
_parser.State.StatusMessageUpdate -= State_StatusMessageUpdate;
361-
}
362-
363-
VBENativeServices.SelectionChanged += _vbe_SelectionChanged;
364-
VBENativeServices.WindowFocusChange += _vbe_FocusChanged;
365-
366194
if (_configService != null)
367195
{
368196
_configService.SettingsChanged -= _configService_SettingsChanged;

RetailCoder.VBE/AppMenu.cs

Lines changed: 23 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,9 @@
11
using System;
22
using System.Collections.Generic;
33
using System.Linq;
4+
using Rubberduck.Parsing;
45
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.UI;
57
using Rubberduck.UI.Command.MenuItems;
68
using Rubberduck.UI.Command.MenuItems.ParentMenus;
79

@@ -10,10 +12,17 @@ namespace Rubberduck
1012
public class AppMenu : IAppMenu, IDisposable
1113
{
1214
private readonly IReadOnlyList<IParentMenuItem> _menus;
15+
private readonly IParseCoordinator _parser;
16+
private readonly ISelectionChangeService _selectionService;
1317

14-
public AppMenu(IEnumerable<IParentMenuItem> menus)
18+
public AppMenu(IEnumerable<IParentMenuItem> menus, IParseCoordinator parser, ISelectionChangeService selectionService)
1519
{
1620
_menus = menus.ToList();
21+
_parser = parser;
22+
_selectionService = selectionService;
23+
24+
_parser.State.StateChanged += OnParserStateChanged;
25+
_selectionService.SelectedDeclarationChanged += OnSelectedDeclarationChange;
1726
}
1827

1928
public void Initialize()
@@ -24,6 +33,16 @@ public void Initialize()
2433
}
2534
}
2635

36+
public void OnSelectedDeclarationChange(object sender, DeclarationChangedEventArgs e)
37+
{
38+
EvaluateCanExecute(_parser.State);
39+
}
40+
41+
private void OnParserStateChanged(object sender, EventArgs e)
42+
{
43+
EvaluateCanExecute(_parser.State);
44+
}
45+
2746
public void EvaluateCanExecute(RubberduckParserState state)
2847
{
2948
foreach (var menu in _menus)
@@ -42,6 +61,9 @@ public void Localize()
4261

4362
public void Dispose()
4463
{
64+
_parser.State.StateChanged -= OnParserStateChanged;
65+
_selectionService.SelectedDeclarationChanged -= OnSelectedDeclarationChange;
66+
4567
// note: doing this wrecks the teardown process. counter-intuitive? sure. but hey it works.
4668
//foreach (var menu in _menus.Where(menu => menu.Item != null))
4769
//{

RetailCoder.VBE/Root/RubberduckModule.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -63,11 +63,12 @@ public override void Load()
6363
Bind<IAddIn>().ToConstant(_addin);
6464
Bind<App>().ToSelf().InSingletonScope();
6565
Bind<RubberduckParserState>().ToSelf().InSingletonScope();
66+
Bind<ISelectionChangeService>().To<SelectionChangeService>().InSingletonScope();
6667
Bind<ISourceControlProvider>().To<GitProvider>();
6768
//Bind<GitProvider>().ToSelf().InSingletonScope();
6869
Bind<TestExplorerModel>().ToSelf().InSingletonScope();
6970
Bind<IOperatingSystem>().To<WindowsOperatingSystem>().InSingletonScope();
70-
71+
7172
Bind<CommandBase>().To<VersionCheckCommand>().WhenInjectedExactlyInto<App>();
7273
BindCodeInspectionTypes();
7374

@@ -175,6 +176,7 @@ private void ApplyDefaultInterfacesConvention(IEnumerable<Assembly> assemblies)
175176
// inspections & factories have their own binding rules
176177
.Where(type => type.Namespace != null
177178
&& !type.Namespace.StartsWith("Rubberduck.VBEditor.SafeComWrappers")
179+
&& !type.Name.Equals("SelectionChangeService")
178180
&& !type.Name.EndsWith("Factory") && !type.Name.EndsWith("ConfigProvider") && !type.GetInterfaces().Contains(typeof(IInspection)))
179181
.BindDefaultInterface()
180182
.Configure(binding => binding.InCallScope())); // TransientScope wouldn't dispose disposables

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -470,6 +470,7 @@
470470
<Compile Include="UI\CodeExplorer\Commands\AddTestModuleCommand.cs" />
471471
<Compile Include="UI\EnvironmentProvider.cs" />
472472
<Compile Include="UI\ModernFolderBrowser.cs" />
473+
<Compile Include="UI\SelectionChangeService.cs" />
473474
<Compile Include="VersionCheck\IVersionCheck.cs" />
474475
<Compile Include="UI\Command\MenuItems\CommandBars\AppCommandBarBase.cs" />
475476
<Compile Include="UI\Command\MenuItems\CommandBars\ContextSelectionLabelMenuItem.cs" />

RetailCoder.VBE/UI/Command/MenuItems/CommandBars/AppCommandBarBase.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
using System;
21
using System.Collections.Generic;
32
using System.Linq;
43
using System.Runtime.InteropServices;
@@ -50,7 +49,7 @@ public void Localize()
5049
}
5150
}
5251

53-
public void Initialize()
52+
public virtual void Initialize()
5453
{
5554
if (Parent == null)
5655
{

0 commit comments

Comments
 (0)