Skip to content

Commit f2a5ef9

Browse files
committed
Merge pull request #10 from rubberduck-vba/next
Pull next
2 parents 194ef85 + d374061 commit f2a5ef9

File tree

74 files changed

+5108
-539
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

74 files changed

+5108
-539
lines changed

RetailCoder.VBE/App.cs

Lines changed: 11 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,7 @@
11
using System;
22
using System.Collections.Concurrent;
3-
using System.Collections.Generic;
4-
using System.Diagnostics;
53
using System.Globalization;
64
using System.Linq;
7-
using System.Runtime.InteropServices;
85
using System.Threading;
96
using System.Threading.Tasks;
107
using System.Windows.Forms;
@@ -87,13 +84,17 @@ private async void hooks_MessageReceived(object sender, HookEventArgs e)
8784
if (_isAwaitingTwoStepKey)
8885
{
8986
// todo: use _firstStepHotKey and e.Key to run 2-step hotkey action
87+
if (_firstStepHotKey == Keys.I && e.Key == Keys.M)
88+
{
89+
_indenter.IndentCurrentModule();
90+
}
9091

9192
AwaitNextKey();
9293
return;
9394
}
9495

9596
var component = _vbe.ActiveCodePane.CodeModule.Parent;
96-
await ParseComponentAsync(component);
97+
ParseComponentAsync(component);
9798

9899
AwaitNextKey();
99100
return;
@@ -148,12 +149,12 @@ private void Parser_StateChanged(object sender, EventArgs e)
148149
_appMenus.EvaluateCanExecute(_parser.State);
149150
}
150151

151-
private async Task ParseComponentAsync(VBComponent component, bool resolve = true)
152+
private void ParseComponentAsync(VBComponent component, bool resolve = true)
152153
{
153154
var tokenSource = RenewTokenSource(component);
154155

155156
var token = tokenSource.Token;
156-
await _parser.ParseAsync(component, token);
157+
_parser.ParseAsync(component, token);
157158

158159
if (resolve && !token.IsCancellationRequested)
159160
{
@@ -195,10 +196,10 @@ public void Startup()
195196
ParseAll();
196197
});
197198

198-
_hooks.AddHook(new LowLevelKeyboardHook(_vbe));
199-
_hooks.AddHook(new HotKey((IntPtr)_vbe.MainWindow.HWnd, "%+R", Keys.R));
200-
_hooks.AddHook(new HotKey((IntPtr)_vbe.MainWindow.HWnd, "%+I", Keys.I));
201-
_hooks.Attach();
199+
//_hooks.AddHook(new LowLevelKeyboardHook(_vbe));
200+
//_hooks.AddHook(new HotKey((IntPtr)_vbe.MainWindow.HWnd, "%^R", Keys.R));
201+
//_hooks.AddHook(new HotKey((IntPtr)_vbe.MainWindow.HWnd, "%^I", Keys.I));
202+
//_hooks.Attach();
202203
}
203204

204205
private void ParseAll()

RetailCoder.VBE/Common/DeclarationExtensions.cs

Lines changed: 190 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,16 @@
11
using System;
22
using System.Collections.Generic;
33
using System.Diagnostics;
4+
using System.Diagnostics.CodeAnalysis;
45
using System.Linq;
56
using System.Windows.Media.Imaging;
67
using Microsoft.Vbe.Interop;
78
using Rubberduck.Annotations;
9+
using Rubberduck.Parsing;
810
using Rubberduck.Parsing.Grammar;
911
using Rubberduck.Parsing.Symbols;
1012
using Rubberduck.VBEditor;
13+
// ReSharper disable LocalizableElement
1114

1215
namespace Rubberduck.Common
1316
{
@@ -20,6 +23,114 @@ public static BitmapImage BitmapImage(this Declaration declaration)
2023
return Cache[declaration];
2124
}
2225

26+
/// <summary>
27+
/// Returns the Selection of a VariableStmtContext.
28+
/// </summary>
29+
/// <exception cref="ArgumentException">Throws when target's DeclarationType is not Variable.</exception>
30+
/// <param name="target"></param>
31+
/// <returns></returns>
32+
public static Selection GetVariableStmtContextSelection(this Declaration target)
33+
{
34+
if (target.DeclarationType != DeclarationType.Variable)
35+
{
36+
throw new ArgumentException("Target DeclarationType is not Variable.", "target");
37+
}
38+
39+
var statement = GetVariableStmtContext(target);
40+
41+
return new Selection(statement.Start.Line, statement.Start.Column,
42+
statement.Stop.Line, statement.Stop.Column);
43+
}
44+
45+
/// <summary>
46+
/// Returns a VariableStmtContext.
47+
/// </summary>
48+
/// <exception cref="ArgumentException">Throws when target's DeclarationType is not Variable.</exception>
49+
/// <param name="target"></param>
50+
/// <returns></returns>
51+
public static VBAParser.VariableStmtContext GetVariableStmtContext(this Declaration target)
52+
{
53+
if (target.DeclarationType != DeclarationType.Variable)
54+
{
55+
throw new ArgumentException("Target DeclarationType is not Variable.", "target");
56+
}
57+
58+
var statement = target.Context.Parent.Parent as VBAParser.VariableStmtContext;
59+
if (statement == null)
60+
{
61+
throw new MissingMemberException("Statement not found");
62+
}
63+
64+
return statement;
65+
}
66+
67+
/// <summary>
68+
/// Returns whether a variable declaration statement contains multiple declarations in a single statement.
69+
/// </summary>
70+
/// <exception cref="ArgumentException">Throws when target's DeclarationType is not Variable.</exception>
71+
/// <param name="target"></param>
72+
/// <returns></returns>
73+
public static bool HasMultipleDeclarationsInStatement(this Declaration target)
74+
{
75+
if (target.DeclarationType != DeclarationType.Variable)
76+
{
77+
throw new ArgumentException("Target DeclarationType is not Variable.", "target");
78+
}
79+
80+
var statement = target.Context.Parent as VBAParser.VariableListStmtContext;
81+
82+
return statement != null && statement.children.OfType<VBAParser.VariableSubStmtContext>().Any();
83+
}
84+
85+
/// <summary>
86+
/// Returns the number of variable declarations in a single statement.
87+
/// </summary>
88+
/// <exception cref="ArgumentException">Throws when target's DeclarationType is not Variable.</exception>
89+
/// <param name="target"></param>
90+
/// <returns></returns>
91+
public static int CountOfDeclarationsInStatement(this Declaration target)
92+
{
93+
if (target.DeclarationType != DeclarationType.Variable)
94+
{
95+
throw new ArgumentException("Target DeclarationType is not Variable.", "target");
96+
}
97+
98+
var statement = target.Context.Parent as VBAParser.VariableListStmtContext;
99+
100+
if (statement != null)
101+
{
102+
return statement.children.OfType<VBAParser.VariableSubStmtContext>().Count();
103+
}
104+
105+
throw new ArgumentException("'target.Context.Parent' is not type VBAParser.VariabelListStmtContext", "target");
106+
}
107+
108+
/// <summary>
109+
/// Returns the number of variable declarations in a single statement. Adjusted to be 1-indexed rather than 0-indexed.
110+
/// </summary>
111+
/// <exception cref="ArgumentException">Throws when target's DeclarationType is not Variable.</exception>
112+
/// <param name="target"></param>
113+
/// <returns></returns>
114+
public static int IndexOfVariableDeclarationInStatement(this Declaration target)
115+
{
116+
if (target.DeclarationType != DeclarationType.Variable)
117+
{
118+
throw new ArgumentException("Target DeclarationType is not Variable.", "target");
119+
}
120+
121+
var statement = target.Context.Parent as VBAParser.VariableListStmtContext;
122+
123+
if (statement != null)
124+
{
125+
return statement.children.OfType<VBAParser.VariableSubStmtContext>()
126+
.ToList()
127+
.IndexOf((VBAParser.VariableSubStmtContext)target.Context) + 1;
128+
}
129+
130+
// ReSharper disable once LocalizableElement
131+
throw new ArgumentException("'target.Context.Parent' is not type VBAParser.VariabelListStmtContext", "target");
132+
}
133+
23134
public static readonly DeclarationType[] ProcedureTypes =
24135
{
25136
DeclarationType.Procedure,
@@ -270,7 +381,15 @@ public static Declaration FindInterfaceMember(this IEnumerable<Declaration> decl
270381
: matches.First();
271382
}
272383

273-
public static Declaration FindSelection(this IEnumerable<Declaration> declarations, QualifiedSelection selection, DeclarationType[] validDeclarationTypes)
384+
/// <summary>
385+
/// Returns the declaration contained in a qualified selection.
386+
/// To get the selection of a variable or field, use FindVariable(QualifiedSelection)
387+
/// </summary>
388+
/// <param name="declarations"></param>
389+
/// <param name="selection"></param>
390+
/// <param name="validDeclarationTypes"></param>
391+
/// <returns></returns>
392+
public static Declaration FindTarget(this IEnumerable<Declaration> declarations, QualifiedSelection selection, DeclarationType[] validDeclarationTypes)
274393
{
275394
var items = declarations.ToList();
276395

@@ -332,5 +451,75 @@ public static Declaration FindSelection(this IEnumerable<Declaration> declaratio
332451
}
333452
return target;
334453
}
454+
455+
/// <summary>
456+
/// Returns the variable which contains the passed-in QualifiedSelection. Returns null if the selection is not on a variable.
457+
/// </summary>
458+
/// <param name="declarations"></param>
459+
/// <param name="selection"></param>
460+
/// <returns></returns>
461+
public static Declaration FindVariable(this IEnumerable<Declaration> declarations, QualifiedSelection selection)
462+
{
463+
var items = declarations.Where(d => !d.IsBuiltIn && d.DeclarationType == DeclarationType.Variable).ToList();
464+
465+
var target = items
466+
.FirstOrDefault(item => item.IsSelected(selection) || item.References.Any(r => r.IsSelected(selection)));
467+
468+
if (target != null) { return target; }
469+
470+
var targets = items.Where(item => item.ComponentName == selection.QualifiedName.ComponentName);
471+
472+
foreach (var declaration in targets)
473+
{
474+
var declarationSelection = new Selection(declaration.Context.Start.Line,
475+
declaration.Context.Start.Column,
476+
declaration.Context.Stop.Line,
477+
declaration.Context.Stop.Column + declaration.Context.Stop.Text.Length);
478+
479+
if (declarationSelection.Contains(selection.Selection) ||
480+
!HasMultipleDeclarationsInStatement(declaration) && GetVariableStmtContextSelection(declaration).Contains(selection.Selection))
481+
{
482+
return declaration;
483+
}
484+
485+
var reference =
486+
declaration.References.FirstOrDefault(r => r.Selection.Contains(selection.Selection));
487+
488+
if (reference != null)
489+
{
490+
return reference.Declaration;
491+
}
492+
}
493+
return null;
494+
}
495+
496+
/// <summary>
497+
/// Returns the interface for a QualifiedSelection contained by a statement similar to "Implements IClass1"
498+
/// </summary>
499+
/// <param name="declarations"></param>
500+
/// <param name="selection"></param>
501+
/// <returns></returns>
502+
[SuppressMessage("ReSharper", "LoopCanBeConvertedToQuery")]
503+
public static Declaration FindInterface(this IEnumerable<Declaration> declarations, QualifiedSelection selection)
504+
{
505+
foreach (var declaration in declarations.FindInterfaces())
506+
{
507+
foreach (var reference in declaration.References)
508+
{
509+
var implementsStmt = reference.Context.Parent as VBAParser.ImplementsStmtContext;
510+
511+
if (implementsStmt == null) { continue; }
512+
513+
if (reference.QualifiedModuleName == selection.QualifiedName &&
514+
(implementsStmt.GetSelection().Contains(selection.Selection)
515+
|| reference.Selection.Contains(selection.Selection)))
516+
{
517+
return declaration;
518+
}
519+
}
520+
}
521+
522+
return null;
523+
}
335524
}
336525
}

RetailCoder.VBE/Common/HookEventArgs.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@ namespace Rubberduck.Common
66
public class HookEventArgs : EventArgs
77
{
88
private readonly Keys _key;
9+
private static readonly Lazy<HookEventArgs> _empty = new Lazy<HookEventArgs>(() => new HookEventArgs(Keys.None));
910

1011
public HookEventArgs(Keys key)
1112
{
@@ -14,6 +15,6 @@ public HookEventArgs(Keys key)
1415

1516
public Keys Key { get { return _key; } }
1617

17-
public new static HookEventArgs Empty {get { return new HookEventArgs(Keys.None); }}
18+
public new static HookEventArgs Empty {get { return _empty.Value; }}
1819
}
1920
}

RetailCoder.VBE/Common/RubberduckHooks.cs

Lines changed: 9 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -11,8 +11,8 @@ public class RubberduckHooks : IRubberduckHooks
1111
{
1212
private readonly IntPtr _mainWindowHandle;
1313

14-
private readonly IntPtr _oldWndPointer;
15-
private readonly User32.WndProc _oldWndProc;
14+
private IntPtr _oldWndPointer;
15+
private User32.WndProc _oldWndProc;
1616
private User32.WndProc _newWndProc;
1717

1818
private readonly ITimerHook _timerHook;
@@ -25,11 +25,7 @@ public class RubberduckHooks : IRubberduckHooks
2525
public RubberduckHooks(IntPtr mainWindowHandle, ITimerHook timerHook)
2626
{
2727
_mainWindowHandle = mainWindowHandle;
28-
_oldWndProc = WindowProc;
2928
_newWndProc = WindowProc;
30-
_oldWndPointer = User32.SetWindowLong(_mainWindowHandle, (int)WindowLongFlags.GWL_WNDPROC, _newWndProc);
31-
_oldWndProc = (User32.WndProc)Marshal.GetDelegateForFunctionPointer(_oldWndPointer, typeof(User32.WndProc));
32-
3329
_timerHook = timerHook;
3430
_timerHook.Tick += timerHook_Tick;
3531
}
@@ -61,6 +57,9 @@ public void Attach()
6157
return;
6258
}
6359

60+
_oldWndPointer = User32.SetWindowLong(_mainWindowHandle, (int)WindowLongFlags.GWL_WNDPROC, _newWndProc);
61+
_oldWndProc = (User32.WndProc)Marshal.GetDelegateForFunctionPointer(_oldWndPointer, typeof(User32.WndProc));
62+
6463
foreach (var hook in Hooks)
6564
{
6665
hook.Attach();
@@ -113,6 +112,8 @@ private void timerHook_Tick(object sender, EventArgs e)
113112

114113
public void Dispose()
115114
{
115+
User32.SetWindowLong(_mainWindowHandle, (int)WindowLongFlags.GWL_WNDPROC, _oldWndProc);
116+
116117
_timerHook.Tick -= timerHook_Tick;
117118
_timerHook.Detach();
118119

@@ -123,7 +124,6 @@ private IntPtr WindowProc(IntPtr hWnd, int uMsg, int wParam, int lParam)
123124
{
124125
try
125126
{
126-
var processed = false;
127127
if (hWnd == _mainWindowHandle)
128128
{
129129
switch ((WM)uMsg)
@@ -136,7 +136,7 @@ private IntPtr WindowProc(IntPtr hWnd, int uMsg, int wParam, int lParam)
136136
{
137137
var args = new HookEventArgs(hook.HotKeyInfo.Keys);
138138
OnMessageReceived(hook, args);
139-
processed = true;
139+
return IntPtr.Zero;
140140
}
141141
}
142142
break;
@@ -152,15 +152,9 @@ private IntPtr WindowProc(IntPtr hWnd, int uMsg, int wParam, int lParam)
152152
Detach();
153153
break;
154154
}
155-
156155
break;
157156
}
158157
}
159-
160-
if (!processed)
161-
{
162-
return User32.CallWindowProc(_oldWndProc, hWnd, uMsg, wParam, lParam);
163-
}
164158
}
165159
catch (Exception exception)
166160
{
@@ -175,9 +169,7 @@ private IntPtr WindowProc(IntPtr hWnd, int uMsg, int wParam, int lParam)
175169
/// </summary>
176170
private static int LoWord(int dw)
177171
{
178-
return (dw & 0x8000) != 0
179-
? 0x8000 | (dw & 0x7FFF)
180-
: dw & 0xFFFF;
172+
return dw & 0xFFFF;
181173
}
182174

183175
private IntPtr GetWindowThread(IntPtr hWnd)

RetailCoder.VBE/Navigation/RegexSearchReplace/RegexSearchReplace.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -132,7 +132,7 @@ private List<RegexSearchResult> SearchCurrentBlock(string searchPattern)
132132

133133
var wrapper = _codePaneFactory.Create(_vbe.ActiveCodePane);
134134
var qualifiedSelection = new QualifiedSelection(new QualifiedModuleName(wrapper.CodeModule.Parent), wrapper.Selection);
135-
dynamic block = parseResult.AllDeclarations.FindSelection(qualifiedSelection, declarationTypes).Context.Parent;
135+
dynamic block = parseResult.AllDeclarations.FindTarget(qualifiedSelection, declarationTypes).Context.Parent;
136136
var selection = new Selection(block.Start.Line, block.Start.Column, block.Stop.Line, block.Stop.Column);
137137
return results.Where(r => selection.Contains(r.Selection)).ToList();
138138
}

0 commit comments

Comments
 (0)