Skip to content

Commit 5216f76

Browse files
committed
Get status bar working (partially - CodePane only). First step in burniating RawInput.
1 parent aade1ca commit 5216f76

File tree

18 files changed

+486
-97
lines changed

18 files changed

+486
-97
lines changed

RetailCoder.VBE/App.cs

Lines changed: 43 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -15,11 +15,13 @@
1515
using System.Windows.Forms;
1616
using Rubberduck.UI.Command;
1717
using Rubberduck.UI.Command.MenuItems.CommandBars;
18+
using Rubberduck.VBEditor.Events;
1819
using Rubberduck.VBEditor.SafeComWrappers;
1920
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
2021
using Rubberduck.VBEditor.SafeComWrappers.MSForms;
2122
using Rubberduck.VBEditor.SafeComWrappers.Office.Core.Abstract;
2223
using Rubberduck.VersionCheck;
24+
using Application = System.Windows.Forms.Application;
2325

2426
namespace Rubberduck
2527
{
@@ -61,7 +63,9 @@ public App(IVBE vbe,
6163
_version = version;
6264
_checkVersionCommand = checkVersionCommand;
6365

64-
_hooks.MessageReceived += _hooks_MessageReceived;
66+
VBEEvents.SelectionChanged += _vbe_SelectionChanged;
67+
VBEEvents.ForgroundWindowChanged += _vbe_ForegroundWindowChanged;
68+
6569
_configService.SettingsChanged += _configService_SettingsChanged;
6670
_parser.State.StateChanged += Parser_StateChanged;
6771
_parser.State.StatusMessageUpdate += State_StatusMessageUpdate;
@@ -81,17 +85,46 @@ private void State_StatusMessageUpdate(object sender, RubberduckStatusMessageEve
8185
_stateBar.SetStatusLabelCaption(message, _parser.State.ModuleExceptions.Count);
8286
}
8387

84-
private void _hooks_MessageReceived(object sender, HookEventArgs e)
88+
private void _vbe_SelectionChanged(object sender, SelectionChangedEventArgs e)
89+
{
90+
RefreshSelection(e.CodePane);
91+
}
92+
93+
private void _vbe_ForegroundWindowChanged(object sender, WindowChangedEventArgs e)
8594
{
86-
RefreshSelection();
95+
RefreshSelection(e.Window);
8796
}
8897

8998
private ParserState _lastStatus;
9099
private Declaration _lastSelectedDeclaration;
91-
92-
private void RefreshSelection()
100+
private void RefreshSelection(ICodePane pane)
93101
{
102+
Declaration selectedDeclaration = null;
103+
if (!pane.IsWrappingNullReference)
104+
{
105+
selectedDeclaration = _parser.State.FindSelectedDeclaration(pane);
106+
var refCount = selectedDeclaration == null ? 0 : selectedDeclaration.References.Count();
107+
var caption = _stateBar.GetContextSelectionCaption(_vbe.ActiveCodePane, selectedDeclaration);
108+
_stateBar.SetContextSelectionCaption(caption, refCount);
109+
}
110+
111+
var currentStatus = _parser.State.Status;
112+
if (ShouldEvaluateCanExecute(selectedDeclaration, currentStatus))
113+
{
114+
_appMenus.EvaluateCanExecute(_parser.State);
115+
_stateBar.EvaluateCanExecute(_parser.State);
116+
}
117+
118+
_lastStatus = currentStatus;
119+
_lastSelectedDeclaration = selectedDeclaration;
120+
}
94121

122+
private void RefreshSelection(IWindow window)
123+
{
124+
if (window.IsWrappingNullReference || window.Type != WindowKind.Designer)
125+
{
126+
return;
127+
}
95128
var caption = String.Empty;
96129
var refCount = 0;
97130

@@ -103,7 +136,7 @@ private void RefreshSelection()
103136

104137
//TODO - I doubt this is the best way to check if the SelectedVBComponent and the ActiveCodePane are the same component.
105138
if (windowKind == WindowKind.CodeWindow || (!_vbe.SelectedVBComponent.IsWrappingNullReference
106-
&& component.ParentProject.ProjectId == pane.CodeModule.Parent.ParentProject.ProjectId
139+
&& component.ParentProject.ProjectId == pane.CodeModule.Parent.ParentProject.ProjectId
107140
&& component.Name == pane.CodeModule.Parent.Name))
108141
{
109142
selectedDeclaration = _parser.State.FindSelectedDeclaration(pane);
@@ -120,13 +153,13 @@ private void RefreshSelection()
120153
{
121154
//The user might have selected the project node in Project Explorer
122155
//If they've chosen a folder, we'll return the project anyway
123-
caption = !_vbe.ActiveVBProject.IsWrappingNullReference
156+
caption = !_vbe.ActiveVBProject.IsWrappingNullReference
124157
? _vbe.ActiveVBProject.Name
125158
: null;
126159
}
127160
else
128161
{
129-
caption = component.Type == ComponentType.UserForm && component.HasOpenDesigner
162+
caption = component.Type == ComponentType.UserForm && component.HasOpenDesigner
130163
? GetComponentControlsCaption(component)
131164
: String.Format("{0}.{1} ({2})", component.ParentProject.Name, component.Name, component.Type);
132165
}
@@ -322,10 +355,8 @@ public void Dispose()
322355
_parser.State.StatusMessageUpdate -= State_StatusMessageUpdate;
323356
}
324357

325-
if (_hooks != null)
326-
{
327-
_hooks.MessageReceived -= _hooks_MessageReceived;
328-
}
358+
VBEEvents.SelectionChanged += _vbe_SelectionChanged;
359+
VBEEvents.ForgroundWindowChanged += _vbe_ForegroundWindowChanged;
329360

330361
if (_configService != null)
331362
{

RetailCoder.VBE/Common/WinAPI/RawInput.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
using System.Collections.Generic;
44
using System.ComponentModel;
55
using System.Runtime.InteropServices;
6-
using Rubberduck.UI;
6+
using Rubberduck.VBEditor.WindowsApi;
77

88
namespace Rubberduck.Common.WinAPI
99
{

RetailCoder.VBE/Common/WinAPI/User32.cs

Lines changed: 0 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -190,36 +190,5 @@ public static class User32
190190
public delegate int WindowEnumProc(IntPtr hwnd, IntPtr lparam);
191191
[DllImport("user32.dll")]
192192
public static extern bool EnumChildWindows(IntPtr hwnd, WindowEnumProc func, IntPtr lParam);
193-
194-
/// <summary>
195-
/// A helper function that returns <c>true</c> when the specified handle is that of the foreground window.
196-
/// </summary>
197-
/// <param name="mainWindowHandle">The handle for the VBE's MainWindow.</param>
198-
/// <returns></returns>
199-
public static bool IsVbeWindowActive(IntPtr mainWindowHandle)
200-
{
201-
uint vbeThread;
202-
GetWindowThreadProcessId(mainWindowHandle, out vbeThread);
203-
204-
uint hThread;
205-
GetWindowThreadProcessId(GetForegroundWindow(), out hThread);
206-
207-
return (IntPtr)hThread == (IntPtr)vbeThread;
208-
}
209-
210-
public enum WindowType
211-
{
212-
Indeterminate,
213-
VbaWindow,
214-
DesignerWindow
215-
}
216-
217-
public static WindowType ToWindowType(this IntPtr hwnd)
218-
{
219-
var name = new StringBuilder(128);
220-
GetClassName(hwnd, name, name.Capacity);
221-
WindowType id;
222-
return Enum.TryParse(name.ToString(), out id) ? id : WindowType.Indeterminate;
223-
}
224193
}
225194
}

RetailCoder.VBE/Extension.cs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@
1818
using NLog;
1919
using Rubberduck.Settings;
2020
using Rubberduck.SettingsProvider;
21+
using Rubberduck.VBEditor.Events;
2122
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
2223

2324
namespace Rubberduck
@@ -53,8 +54,9 @@ public void OnConnection(object Application, ext_ConnectMode ConnectMode, object
5354
{
5455
if (Application is Microsoft.Vbe.Interop.VBE)
5556
{
56-
var vbe = (Microsoft.Vbe.Interop.VBE) Application;
57+
var vbe = (Microsoft.Vbe.Interop.VBE) Application;
5758
_ide = new VBEditor.SafeComWrappers.VBA.VBE(vbe);
59+
VBEEvents.HookEvents(_ide);
5860

5961
var addin = (Microsoft.Vbe.Interop.AddIn)AddInInst;
6062
_addin = new VBEditor.SafeComWrappers.VBA.AddIn(addin) { Object = this };
@@ -87,7 +89,7 @@ public void OnConnection(object Application, ext_ConnectMode ConnectMode, object
8789

8890
Assembly LoadFromSameFolder(object sender, ResolveEventArgs args)
8991
{
90-
var folderPath = Path.GetDirectoryName(Assembly.GetExecutingAssembly().Location);
92+
var folderPath = Path.GetDirectoryName(Assembly.GetExecutingAssembly().Location) ?? string.Empty;
9193
var assemblyPath = Path.Combine(folderPath, new AssemblyName(args.Name).Name + ".dll");
9294
if (!File.Exists(assemblyPath))
9395
{
@@ -219,6 +221,8 @@ private void Startup()
219221

220222
private void ShutdownAddIn()
221223
{
224+
VBEEvents.UnhookEvents();
225+
222226
var currentDomain = AppDomain.CurrentDomain;
223227
currentDomain.AssemblyResolve -= LoadFromSameFolder;
224228

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -370,7 +370,6 @@
370370
<Compile Include="Common\KeyHookEventArgs.cs" />
371371
<Compile Include="Common\WinAPI\User32.cs" />
372372
<Compile Include="Common\WinAPI\WindowLongFlags.cs" />
373-
<Compile Include="Common\WinAPI\WM.cs" />
374373
<Compile Include="Common\WindowsOperatingSystem.cs" />
375374
<Compile Include="Common\UndocumentedAttribute.cs" />
376375
<Compile Include="Inspections\ApplicationWorksheetFunctionInspection.cs" />
@@ -500,7 +499,6 @@
500499
<Compile Include="UI\CodeExplorer\Commands\AddClassModuleCommand.cs" />
501500
<Compile Include="UI\CodeExplorer\Commands\AddStdModuleCommand.cs" />
502501
<Compile Include="UI\CodeExplorer\Commands\AddTestModuleCommand.cs" />
503-
<Compile Include="UI\SubclassingWindow.cs" />
504502
<Compile Include="VersionCheck\IVersionCheck.cs" />
505503
<Compile Include="UI\Command\MenuItems\CommandBars\AppCommandBarBase.cs" />
506504
<Compile Include="UI\Command\MenuItems\CommandBars\ContextSelectionLabelMenuItem.cs" />
Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using System.Text;
5+
using System.Threading.Tasks;
6+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
7+
8+
namespace Rubberduck.VBEditor.Events
9+
{
10+
public class SelectionChangedEventArgs : EventArgs
11+
{
12+
public ICodePane CodePane { get; private set; }
13+
14+
public SelectionChangedEventArgs(ICodePane pane)
15+
{
16+
CodePane = pane;
17+
}
18+
}
19+
}
Lines changed: 155 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,155 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Diagnostics;
4+
using System.Linq;
5+
using System.Text;
6+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
7+
using Rubberduck.VBEditor.WindowsApi;
8+
9+
namespace Rubberduck.VBEditor.Events
10+
{
11+
public static class VBEEvents
12+
{
13+
private static User32.WinEventProc _eventProc;
14+
private static IntPtr _eventHandle;
15+
private static IVBE _vbe;
16+
17+
public struct WindowInfo
18+
{
19+
private readonly IntPtr _handle;
20+
private readonly IWindow _window;
21+
22+
public IntPtr Hwnd { get { return _handle; } }
23+
public IWindow Window { get { return _window; } }
24+
25+
public WindowInfo(IntPtr handle, IWindow window)
26+
{
27+
_handle = handle;
28+
_window = window;
29+
}
30+
}
31+
32+
//This *could* be a ConcurrentDictionary, but there other operations that need the lock around it anyway.
33+
private static readonly Dictionary<IntPtr, WindowInfo> TrackedWindows = new Dictionary<IntPtr, WindowInfo>();
34+
private static readonly object ThreadLock = new object();
35+
36+
private static uint _threadId;
37+
38+
public static void HookEvents(IVBE vbe)
39+
{
40+
_vbe = vbe;
41+
if (_eventHandle == IntPtr.Zero)
42+
{
43+
_eventProc = VbeEventCallback;
44+
_threadId = User32.GetWindowThreadProcessId(new IntPtr(_vbe.MainWindow.HWnd), IntPtr.Zero);
45+
_eventHandle = User32.SetWinEventHook((uint)WinEvent.Min, (uint)WinEvent.Max, IntPtr.Zero, _eventProc, 0, _threadId, WinEventFlags.OutOfContext);
46+
}
47+
}
48+
49+
public static void UnhookEvents()
50+
{
51+
User32.UnhookWinEvent(_eventHandle);
52+
}
53+
54+
public static void VbeEventCallback(IntPtr hWinEventHook, uint eventType, IntPtr hwnd, int idObject, int idChild,
55+
uint dwEventThread, uint dwmsEventTime)
56+
{
57+
if (hwnd != IntPtr.Zero && idObject == (int)ObjId.Caret && eventType == (uint)WinEvent.ObjectLocationChange && hwnd.ToWindowType() == WindowType.VbaWindow)
58+
{
59+
OnSelectionChanged(hwnd);
60+
}
61+
else if (idObject == (int)ObjId.Window &&
62+
(eventType == (uint)WinEvent.ObjectCreate || eventType == (uint)WinEvent.ObjectDestroy) &&
63+
hwnd.ToWindowType() != WindowType.Indeterminate)
64+
{
65+
if (eventType == (uint) WinEvent.ObjectCreate)
66+
{
67+
AttachWindow(hwnd);
68+
}
69+
else if (eventType == (uint)WinEvent.ObjectDestroy)
70+
{
71+
DetachWindow(hwnd);
72+
}
73+
}
74+
}
75+
76+
private static void AttachWindow(IntPtr hwnd)
77+
{
78+
lock (ThreadLock)
79+
{
80+
Debug.Assert(!TrackedWindows.ContainsKey(hwnd));
81+
var window = GetWindowFromHwnd(hwnd);
82+
if (window == null) return;
83+
var info = new WindowInfo(hwnd, window);
84+
TrackedWindows.Add(hwnd, info);
85+
}
86+
}
87+
88+
private static void DetachWindow(IntPtr hwnd)
89+
{
90+
lock (ThreadLock)
91+
{
92+
Debug.Assert(TrackedWindows.ContainsKey(hwnd));
93+
TrackedWindows.Remove(hwnd);
94+
}
95+
}
96+
97+
public static event EventHandler<SelectionChangedEventArgs> SelectionChanged;
98+
private static void OnSelectionChanged(IntPtr hwnd)
99+
{
100+
if (SelectionChanged != null)
101+
{
102+
var pane = GetCodePaneFromHwnd(hwnd);
103+
SelectionChanged.Invoke(_vbe, new SelectionChangedEventArgs(pane));
104+
}
105+
}
106+
107+
//Pending location of a suitable event - might need a subclass here instead.
108+
public static event EventHandler<WindowChangedEventArgs> ForgroundWindowChanged;
109+
private static void OnForgroundWindowChanged(WindowInfo info)
110+
{
111+
if (ForgroundWindowChanged != null)
112+
{
113+
ForgroundWindowChanged.Invoke(_vbe, new WindowChangedEventArgs(info.Hwnd, info.Window));
114+
}
115+
}
116+
117+
private static ICodePane GetCodePaneFromHwnd(IntPtr hwnd)
118+
{
119+
var caption = hwnd.GetWindowText();
120+
return _vbe.CodePanes.FirstOrDefault(x => x.Window.Caption.Equals(caption));
121+
}
122+
123+
private static IWindow GetWindowFromHwnd(IntPtr hwnd)
124+
{
125+
var caption = hwnd.GetWindowText();
126+
return _vbe.Windows.FirstOrDefault(x => x.Caption.Equals(caption));
127+
}
128+
129+
/// <summary>
130+
/// A helper function that returns <c>true</c> when the specified handle is that of the foreground window.
131+
/// </summary>
132+
/// <returns>True if the active thread is on the VBE's thread.</returns>
133+
public static bool IsVbeWindowActive()
134+
{
135+
uint hThread;
136+
User32.GetWindowThreadProcessId(User32.GetForegroundWindow(), out hThread);
137+
return (IntPtr)hThread == (IntPtr)_threadId;
138+
}
139+
140+
public enum WindowType
141+
{
142+
Indeterminate,
143+
VbaWindow,
144+
DesignerWindow
145+
}
146+
147+
public static WindowType ToWindowType(this IntPtr hwnd)
148+
{
149+
var name = new StringBuilder(128);
150+
User32.GetClassName(hwnd, name, name.Capacity);
151+
WindowType id;
152+
return Enum.TryParse(name.ToString(), out id) ? id : WindowType.Indeterminate;
153+
}
154+
}
155+
}

0 commit comments

Comments
 (0)