Skip to content

Commit d203f5a

Browse files
authored
Merge pull request #221 from rubberduck-vba/next
sync with main repo
2 parents 6af2778 + 1c2a2a7 commit d203f5a

34 files changed

+928
-207
lines changed

RetailCoder.VBE/App.cs

Lines changed: 54 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.WindowFocusChange += _vbe_FocusChanged;
68+
6569
_configService.SettingsChanged += _configService_SettingsChanged;
6670
_parser.State.StateChanged += Parser_StateChanged;
6771
_parser.State.StatusMessageUpdate += State_StatusMessageUpdate;
@@ -81,17 +85,57 @@ 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)
8589
{
86-
RefreshSelection();
90+
RefreshSelection(e.CodePane);
91+
}
92+
93+
private void _vbe_FocusChanged(object sender, WindowChangedEventArgs e)
94+
{
95+
if (e.EventType == WindowChangedEventArgs.FocusType.GotFocus)
96+
{
97+
switch (e.Window.Type)
98+
{
99+
case WindowKind.Designer:
100+
RefreshSelection(e.Window);
101+
break;
102+
case WindowKind.CodeWindow:
103+
RefreshSelection(e.CodePane);
104+
break;
105+
}
106+
}
87107
}
88108

89109
private ParserState _lastStatus;
90110
private Declaration _lastSelectedDeclaration;
91-
92-
private void RefreshSelection()
111+
private void RefreshSelection(ICodePane pane)
93112
{
113+
Declaration selectedDeclaration = null;
114+
if (!pane.IsWrappingNullReference)
115+
{
116+
selectedDeclaration = _parser.State.FindSelectedDeclaration(pane);
117+
var refCount = selectedDeclaration == null ? 0 : selectedDeclaration.References.Count();
118+
var caption = _stateBar.GetContextSelectionCaption(_vbe.ActiveCodePane, selectedDeclaration);
119+
_stateBar.SetContextSelectionCaption(caption, refCount);
120+
}
121+
122+
var currentStatus = _parser.State.Status;
123+
if (ShouldEvaluateCanExecute(selectedDeclaration, currentStatus))
124+
{
125+
_appMenus.EvaluateCanExecute(_parser.State);
126+
_stateBar.EvaluateCanExecute(_parser.State);
127+
}
128+
129+
_lastStatus = currentStatus;
130+
_lastSelectedDeclaration = selectedDeclaration;
131+
}
94132

133+
private void RefreshSelection(IWindow window)
134+
{
135+
if (window.IsWrappingNullReference || window.Type != WindowKind.Designer)
136+
{
137+
return;
138+
}
95139
var caption = String.Empty;
96140
var refCount = 0;
97141

@@ -103,7 +147,7 @@ private void RefreshSelection()
103147

104148
//TODO - I doubt this is the best way to check if the SelectedVBComponent and the ActiveCodePane are the same component.
105149
if (windowKind == WindowKind.CodeWindow || (!_vbe.SelectedVBComponent.IsWrappingNullReference
106-
&& component.ParentProject.ProjectId == pane.CodeModule.Parent.ParentProject.ProjectId
150+
&& component.ParentProject.ProjectId == pane.CodeModule.Parent.ParentProject.ProjectId
107151
&& component.Name == pane.CodeModule.Parent.Name))
108152
{
109153
selectedDeclaration = _parser.State.FindSelectedDeclaration(pane);
@@ -120,13 +164,13 @@ private void RefreshSelection()
120164
{
121165
//The user might have selected the project node in Project Explorer
122166
//If they've chosen a folder, we'll return the project anyway
123-
caption = !_vbe.ActiveVBProject.IsWrappingNullReference
167+
caption = !_vbe.ActiveVBProject.IsWrappingNullReference
124168
? _vbe.ActiveVBProject.Name
125169
: null;
126170
}
127171
else
128172
{
129-
caption = component.Type == ComponentType.UserForm && component.HasOpenDesigner
173+
caption = component.Type == ComponentType.UserForm && component.HasOpenDesigner
130174
? GetComponentControlsCaption(component)
131175
: String.Format("{0}.{1} ({2})", component.ParentProject.Name, component.Name, component.Type);
132176
}
@@ -322,10 +366,8 @@ public void Dispose()
322366
_parser.State.StatusMessageUpdate -= State_StatusMessageUpdate;
323367
}
324368

325-
if (_hooks != null)
326-
{
327-
_hooks.MessageReceived -= _hooks_MessageReceived;
328-
}
369+
VBEEvents.SelectionChanged += _vbe_SelectionChanged;
370+
VBEEvents.WindowFocusChange += _vbe_FocusChanged;
329371

330372
if (_configService != null)
331373
{

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

Lines changed: 61 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,11 @@
11
using Antlr4.Runtime;
2+
using Antlr4.Runtime.Tree;
23
using Rubberduck.Inspections.Abstract;
34
using Rubberduck.Inspections.Resources;
45
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.Parsing.Symbols;
57
using Rubberduck.VBEditor;
6-
using System.Text.RegularExpressions;
8+
using System.Linq;
79

810
namespace Rubberduck.Inspections.QuickFixes
911
{
@@ -12,31 +14,75 @@ namespace Rubberduck.Inspections.QuickFixes
1214
/// </summary>
1315
public class PassParameterByReferenceQuickFix : QuickFixBase
1416
{
15-
public PassParameterByReferenceQuickFix(ParserRuleContext context, QualifiedSelection selection)
16-
: base(context, selection, InspectionsUI.PassParameterByReferenceQuickFix)
17+
private Declaration _target;
18+
19+
public PassParameterByReferenceQuickFix(Declaration target, QualifiedSelection selection)
20+
: base(target.Context, selection, InspectionsUI.PassParameterByReferenceQuickFix)
1721
{
22+
_target = target;
1823
}
1924

2025
public override void Fix()
2126
{
22-
var parameter = Context.GetText();
27+
var argCtxt = GetArgContextForIdentifier(Context.Parent.Parent, _target.IdentifierName);
2328

24-
var parts = parameter.Split(new char[]{' '},2);
25-
if (1 != parts.GetUpperBound(0))
26-
{
27-
return;
28-
}
29-
parts[0] = parts[0].Replace(Tokens.ByVal, Tokens.ByRef);
30-
var newContent = parts[0] + " " + parts[1];
29+
var terminalNode = argCtxt.BYVAL();
3130

32-
var selection = Selection.Selection;
31+
var replacementLine = GenerateByRefReplacementLine(terminalNode);
32+
33+
ReplaceModuleLine(terminalNode.Symbol.Line, replacementLine);
34+
35+
}
36+
private VBAParser.ArgContext GetArgContextForIdentifier(RuleContext context, string identifier)
37+
{
38+
var argList = GetArgListForContext(context);
39+
return argList.arg().SingleOrDefault(parameter =>
40+
Identifier.GetName(parameter).Equals(identifier));
41+
}
42+
private string GenerateByRefReplacementLine(ITerminalNode terminalNode)
43+
{
44+
var module = Selection.QualifiedName.Component.CodeModule;
45+
var byValTokenLine = module.GetLines(terminalNode.Symbol.Line, 1);
3346

47+
return ReplaceAtIndex(byValTokenLine, Tokens.ByVal, Tokens.ByRef, terminalNode.Symbol.Column);
48+
}
49+
private void ReplaceModuleLine(int lineNumber, string replacementLine)
50+
{
3451
var module = Selection.QualifiedName.Component.CodeModule;
52+
module.DeleteLines(lineNumber);
53+
module.InsertLines(lineNumber, replacementLine);
54+
}
55+
private string ReplaceAtIndex(string input, string toReplace, string replacement, int startIndex)
56+
{
57+
int stopIndex = startIndex + toReplace.Length;
58+
var prefix = input.Substring(0, startIndex);
59+
var suffix = input.Substring(stopIndex + 1);
60+
var tokenToBeReplaced = input.Substring(startIndex, stopIndex - startIndex + 1);
61+
return prefix + tokenToBeReplaced.Replace(toReplace, replacement) + suffix;
62+
}
63+
private VBAParser.ArgListContext GetArgListForContext(RuleContext context)
64+
{
65+
if (context is VBAParser.SubStmtContext)
66+
{
67+
return ((VBAParser.SubStmtContext)context).argList();
68+
}
69+
else if (context is VBAParser.FunctionStmtContext)
70+
{
71+
return ((VBAParser.FunctionStmtContext)context).argList();
72+
}
73+
else if (context is VBAParser.PropertyLetStmtContext)
74+
{
75+
return ((VBAParser.PropertyLetStmtContext)context).argList();
76+
}
77+
else if (context is VBAParser.PropertyGetStmtContext)
78+
{
79+
return ((VBAParser.PropertyGetStmtContext)context).argList();
80+
}
81+
else if (context is VBAParser.PropertySetStmtContext)
3582
{
36-
var lines = module.GetLines(selection.StartLine, selection.LineCount);
37-
var result = lines.Replace(parameter, newContent);
38-
module.ReplaceLine(selection.StartLine, result);
83+
return ((VBAParser.PropertySetStmtContext)context).argList();
3984
}
85+
return null;
4086
}
4187
}
4288
}

RetailCoder.VBE/Inspections/Results/AssignedByValParameterInspectionResult.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ public override IEnumerable<QuickFixBase> QuickFixes
2828
return _quickFixes ?? (_quickFixes = new QuickFixBase[]
2929
{
3030
new AssignedByValParameterQuickFix(Target, QualifiedSelection),
31-
new PassParameterByReferenceQuickFix(Target.Context, QualifiedSelection),
31+
new PassParameterByReferenceQuickFix(Target, QualifiedSelection),
3232
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName)
3333
});
3434
}

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" />

RetailCoder.VBE/UI/DockableToolwindowPresenter.cs

Lines changed: 0 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -130,16 +130,6 @@ protected virtual void Dispose(bool disposing)
130130
}
131131
if (disposing && _window != null)
132132
{
133-
if (_userControlObject != null)
134-
{
135-
((_DockableWindowHost)_userControlObject).Dispose();
136-
}
137-
_userControlObject = null;
138-
139-
if (_userControl != null)
140-
{
141-
_userControl.Dispose();
142-
}
143133
// cleanup unmanaged resource wrappers
144134
_window.Close();
145135
_window.Release(true);

RetailCoder.VBE/UI/DockableWindowHost.cs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,8 @@
55
using System.Windows.Forms;
66
using Rubberduck.Common.WinAPI;
77
using Rubberduck.VBEditor;
8+
using Rubberduck.VBEditor.WindowsApi;
9+
using User32 = Rubberduck.Common.WinAPI.User32;
810

911
namespace Rubberduck.UI
1012
{
@@ -52,6 +54,7 @@ private struct LParam
5254

5355
private IntPtr _parentHandle;
5456
private ParentWindow _subClassingWindow;
57+
private GCHandle _thisHandle;
5558

5659
internal void AddUserControl(UserControl control, IntPtr vbeHwnd)
5760
{
@@ -63,7 +66,7 @@ internal void AddUserControl(UserControl control, IntPtr vbeHwnd)
6366
//since we have to inherit from UserControl we don't have to keep handling window messages until the VBE gets
6467
//around to destroying the control's host or it results in an access violation when the base class is disposed.
6568
//We need to manually call base.Dispose() ONLY in response to a WM_DESTROY message.
66-
GC.KeepAlive(this);
69+
_thisHandle = GCHandle.Alloc(this, GCHandleType.Normal);
6770

6871
if (control != null)
6972
{
@@ -143,7 +146,7 @@ protected override void DefWndProc(ref Message m)
143146
//See the comment in the ctor for why we have to listen for this.
144147
if (m.Msg == (int) WM.DESTROY)
145148
{
146-
base.Dispose(true);
149+
_thisHandle.Free();
147150
return;
148151
}
149152
base.DefWndProc(ref m);

0 commit comments

Comments
 (0)