Skip to content

Commit 35f188f

Browse files
committed
*actually* fixes #4468
1 parent 8c69af0 commit 35f188f

File tree

3 files changed

+98
-49
lines changed

3 files changed

+98
-49
lines changed

Rubberduck.Core/AutoComplete/Service/SelfClosingPairCompletionService.cs

Lines changed: 13 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -70,13 +70,7 @@ public bool Execute(SelfClosingPair pair, CodeString original, Keys input, out C
7070
return false;
7171
}
7272

73-
if (input == Keys.Back)
74-
{
75-
result = HandleBackspace(pair, original);
76-
return true;
77-
}
78-
79-
return false;
73+
return input == Keys.Back && HandleBackspace(pair, original, out result);
8074
}
8175

8276
private bool HandleOpeningChar(SelfClosingPair pair, CodeString original, out CodeString result)
@@ -130,16 +124,17 @@ private bool HandleClosingChar(SelfClosingPair pair, CodeString original, out Co
130124
return false;
131125
}
132126

133-
private CodeString HandleBackspace(SelfClosingPair pair, CodeString original)
127+
private bool HandleBackspace(SelfClosingPair pair, CodeString original, out CodeString result)
134128
{
129+
result = null;
135130
var position = original.CaretPosition;
136131
var lines = original.Lines;
137132

138133
var line = lines[original.CaretPosition.StartLine];
139134
if (line.Length == 0)
140135
{
141136
// nothing to delete at caret position... bail out.
142-
return null;
137+
return false;
143138
}
144139

145140
var previous = Math.Max(0, position.StartColumn - 1);
@@ -155,24 +150,25 @@ private CodeString HandleBackspace(SelfClosingPair pair, CodeString original)
155150
if (line.Length == 2)
156151
{
157152
// entire line consists in the self-closing pair itself.
158-
return new CodeString(string.Empty, default, Selection.Empty.ShiftRight());
153+
result = new CodeString(string.Empty, default, Selection.Empty.ShiftRight());
159154
}
160155

161156
// simple case; caret is between the opening and closing chars - remove both.
162157
lines[original.CaretPosition.StartLine] = line.Remove(previous, 2);
163-
return new CodeString(string.Join("\r\n", lines), original.CaretPosition.ShiftLeft(), original.SnippetPosition);
158+
result = new CodeString(string.Join("\r\n", lines), original.CaretPosition.ShiftLeft(), original.SnippetPosition);
164159
}
165160

166161
if (previous < line.Length - 1 && previousChar == pair.OpeningChar)
167162
{
168-
return DeleteMatchingTokensMultiline(pair, original);
163+
return DeleteMatchingTokensMultiline(pair, original, out result);
169164
}
170165

171-
return null;
166+
return result != null;
172167
}
173168

174-
private CodeString DeleteMatchingTokensMultiline(SelfClosingPair pair, CodeString original)
169+
private bool DeleteMatchingTokensMultiline(SelfClosingPair pair, CodeString original, out CodeString result)
175170
{
171+
result = null;
176172
var position = original.CaretPosition;
177173
var lines = original.Lines;
178174
var line = lines[original.CaretPosition.StartLine];
@@ -186,7 +182,7 @@ private CodeString DeleteMatchingTokensMultiline(SelfClosingPair pair, CodeStrin
186182
if (closingTokenPosition == default)
187183
{
188184
// could not locate the closing token... bail out.
189-
return null;
185+
return false;
190186
}
191187

192188
var closingLine = lines[closingTokenPosition.EndLine].Remove(closingTokenPosition.StartColumn, 1);
@@ -252,8 +248,9 @@ private CodeString DeleteMatchingTokensMultiline(SelfClosingPair pair, CodeStrin
252248
// remove any dangling empty lines...
253249
lines = lines.Where((x, i) => i <= position.StartLine || !string.IsNullOrWhiteSpace(x)).ToArray();
254250

255-
return new CodeString(string.Join("\r\n", lines), finalCaretPosition,
251+
result = new CodeString(string.Join("\r\n", lines), finalCaretPosition,
256252
new Selection(original.SnippetPosition.StartLine, 1, original.SnippetPosition.EndLine, 1));
253+
return true;
257254
}
258255

259256
private static Selection HandleBackspaceContinuations(string[] nonEmptyLines, Selection finalCaretPosition)

Rubberduck.Core/AutoComplete/Service/SelfClosingPairHandler.cs

Lines changed: 30 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
using System.Collections.Generic;
2+
using System.Diagnostics;
23
using System.Linq;
34
using Rubberduck.Settings;
45
using Rubberduck.VBEditor;
@@ -9,22 +10,23 @@ namespace Rubberduck.AutoComplete.Service
910
{
1011
public class SelfClosingPairHandler : AutoCompleteHandlerBase
1112
{
12-
private readonly IDictionary<char, SelfClosingPair> _selfClosingPairs;
13+
private readonly IReadOnlyList<SelfClosingPair> _selfClosingPairs;
14+
private readonly IDictionary<char, SelfClosingPair> _scpInputLookup;
1315
private readonly SelfClosingPairCompletionService _scpService;
1416

1517
public SelfClosingPairHandler(ICodePaneHandler pane, SelfClosingPairCompletionService scpService)
1618
: base(pane)
1719
{
18-
var pairs = new[]
20+
_selfClosingPairs = new[]
1921
{
2022
new SelfClosingPair('(', ')'),
2123
new SelfClosingPair('"', '"'),
2224
new SelfClosingPair('[', ']'),
2325
new SelfClosingPair('{', '}'),
2426
};
25-
_selfClosingPairs = pairs
27+
_scpInputLookup = _selfClosingPairs
2628
.Select(p => new {Key = p.OpeningChar, Pair = p})
27-
.Union(pairs.Where(p => !p.IsSymetric).Select(p => new {Key = p.ClosingChar, Pair = p}))
29+
.Union(_selfClosingPairs.Where(p => !p.IsSymetric).Select(p => new {Key = p.ClosingChar, Pair = p}))
2830
.ToDictionary(p => p.Key, p => p.Pair);
2931

3032
_scpService = scpService;
@@ -33,15 +35,34 @@ public SelfClosingPairHandler(ICodePaneHandler pane, SelfClosingPairCompletionSe
3335
public override bool Handle(AutoCompleteEventArgs e, AutoCompleteSettings settings, out CodeString result)
3436
{
3537
result = null;
36-
if (!_selfClosingPairs.TryGetValue(e.Character, out var pair) && e.Character != '\b')
38+
if (!_scpInputLookup.TryGetValue(e.Character, out var pair) && e.Character != '\b')
3739
{
3840
return false;
3941
}
4042

4143
var original = CodePaneHandler.GetCurrentLogicalLine(e.Module);
42-
if (!HandleInternal(e, original, pair, out result))
44+
45+
if (pair != null)
4346
{
44-
return false;
47+
if (!HandleInternal(e, original, pair, out result))
48+
{
49+
return false;
50+
}
51+
}
52+
else if (e.Character == '\b')
53+
{
54+
foreach (var scp in _selfClosingPairs)
55+
{
56+
if (HandleInternal(e, original, scp, out result))
57+
{
58+
break;
59+
}
60+
}
61+
62+
if (result == null)
63+
{
64+
return false;
65+
}
4566
}
4667

4768
var snippetPosition = new Selection(result.SnippetPosition.StartLine, 1, result.SnippetPosition.EndLine, 1);
@@ -87,7 +108,8 @@ private bool HandleInternal(AutoCompleteEventArgs e, CodeString original, SelfCl
87108
e.Character == pair.OpeningChar &&
88109
!result.CaretLine.EndsWith($"{pair.OpeningChar}{pair.ClosingChar}"))
89110
{
90-
// VBE eats it. just bail out.
111+
// VBE eats it. bail out but still swallow the keypress, since we've already re-prettified.
112+
e.Handled = true;
91113
result = null;
92114
return false;
93115
}

RubberduckTests/AutoComplete/SelfClosingPairHandlerTests.cs

Lines changed: 55 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -9,36 +9,62 @@
99

1010
namespace RubberduckTests.AutoComplete
1111
{
12-
[TestFixture]
13-
public class SelfClosingPairHandlerTests
12+
public class SelfClosingPairTestInfo
1413
{
15-
private bool Run(CodeString original, CodeString prettified, char input, CodeString rePrettified, out TestCodeString testResult, bool isControlKeyDown = false, bool isDeleteKey = false)
16-
{
17-
var service = new Mock<SelfClosingPairCompletionService>();
18-
return Run(service, original, prettified, input, rePrettified, out testResult, isControlKeyDown, isDeleteKey);
19-
}
14+
public SelfClosingPairTestInfo(CodeString original, char input, CodeString rePrettified)
15+
: this(new Mock<SelfClosingPairCompletionService>(), original, original, input, rePrettified) { }
2016

21-
private bool Run(Mock<SelfClosingPairCompletionService> service, CodeString original, CodeString prettified, char input, CodeString rePrettified, out TestCodeString testResult, bool isControlKeyDown = false, bool isDeleteKey = false)
17+
public SelfClosingPairTestInfo(CodeString original, char input)
18+
: this(new Mock<SelfClosingPairCompletionService>(), original, original, input, original) { }
19+
20+
public SelfClosingPairTestInfo(CodeString original, CodeString prettified, char input)
21+
: this(new Mock<SelfClosingPairCompletionService>(), original, prettified, input, prettified) { }
22+
23+
public SelfClosingPairTestInfo(Mock<SelfClosingPairCompletionService> service, CodeString original, CodeString prettified, char input, CodeString rePrettified, bool isControlKeyDown = false, bool isDeleteKey = false)
2224
{
23-
var module = new Mock<ICodeModule>();
24-
var handler = new Mock<ICodePaneHandler>();
25-
handler.Setup(e => e.GetCurrentLogicalLine(module.Object)).Returns(original);
26-
handler.SetupSequence(e => e.Prettify(module.Object, It.IsAny<CodeString>()))
25+
Original = original;
26+
Prettified = prettified;
27+
Input = input;
28+
RePrettified = rePrettified;
29+
Settings = AutoCompleteSettings.AllEnabled;
30+
31+
Service = service;
32+
Module = new Mock<ICodeModule>();
33+
Handler = new Mock<ICodePaneHandler>();
34+
Handler.Setup(e => e.GetCurrentLogicalLine(Module.Object)).Returns(original);
35+
Handler.SetupSequence(e => e.Prettify(Module.Object, It.IsAny<CodeString>()))
2736
.Returns(prettified)
2837
.Returns(rePrettified);
2938

30-
var settings = AutoCompleteSettings.AllEnabled;
39+
Args = new AutoCompleteEventArgs(Module.Object, input, isControlKeyDown, isDeleteKey);
40+
}
41+
42+
public Mock<ICodeModule> Module { get; set; }
43+
public Mock<SelfClosingPairCompletionService> Service { get; set; }
44+
public Mock<ICodePaneHandler> Handler { get; set; }
45+
public CodeString Original { get; set; }
46+
public CodeString Prettified { get; set; }
47+
public char Input { get; set; }
48+
public CodeString RePrettified { get; set; }
49+
public AutoCompleteEventArgs Args { get; set; }
50+
public AutoCompleteSettings Settings { get; set; }
3151

32-
var args = new AutoCompleteEventArgs(module.Object, input, isControlKeyDown, isDeleteKey);
33-
var sut = new SelfClosingPairHandler(handler.Object, service.Object);
52+
public TestCodeString Result { get; set; }
53+
}
3454

35-
if (sut.Handle(args, settings, out var result))
55+
[TestFixture]
56+
public class SelfClosingPairHandlerTests
57+
{
58+
private bool Run(SelfClosingPairTestInfo info)
59+
{
60+
var sut = new SelfClosingPairHandler(info.Handler.Object, info.Service.Object);
61+
if (sut.Handle(info.Args, info.Settings, out var result))
3662
{
37-
testResult = new TestCodeString(result);
63+
info.Result = new TestCodeString(result);
3864
return true;
3965
}
4066

41-
testResult = null;
67+
info.Result = null;
4268
return false;
4369
}
4470

@@ -47,9 +73,10 @@ public void GivenInvalidInput_ResultIsNull()
4773
{
4874
var input = 'A'; // note: not a self-closing pair opening or closing character, not a handled key (e.g. '\b').
4975
var original = "DoSomething |".ToCodeString();
76+
var info = new SelfClosingPairTestInfo(original, input);
5077

51-
Assert.IsFalse(Run(original, original, input, original, out var result));
52-
Assert.IsNull(result);
78+
Assert.IsFalse(Run(info));
79+
Assert.IsNull(info.Result);
5380
}
5481

5582
[Test]
@@ -58,20 +85,23 @@ public void GivenValidInput_InvokesSCP()
5885
var input = '"'; // note: not a self-closing pair opening or closing character, not a handled key (e.g. '\b').
5986
var original = "DoSomething |".ToCodeString();
6087
var rePrettified = @"DoSomething ""|""".ToCodeString();
88+
var info = new SelfClosingPairTestInfo(original, input, rePrettified);
6189

62-
Assert.IsTrue(Run(original, original, input, rePrettified, out var result));
63-
Assert.IsNotNull(result);
90+
Assert.IsTrue(Run(info));
91+
Assert.IsNotNull(info.Result);
6492
}
6593

6694
[Test]
67-
public void GivenOpeningParenthesisOnOtherwiseNonEmptyLine_ReturnsFalse()
95+
public void GivenOpeningParenthesisOnOtherwiseNonEmptyLine_ReturnsFalseAndSwallowsKeypress()
6896
{
6997
var input = '(';
7098
var original = "foo = DateSerial(Year|)".ToCodeString();
7199
var rePrettified = "foo = DateSerial(Year(|))".ToCodeString();
100+
var info = new SelfClosingPairTestInfo(original, input, rePrettified);
72101

73-
Assert.IsFalse(Run(original, original, input, rePrettified, out var result));
74-
Assert.IsNull(result);
102+
Assert.IsFalse(Run(info));
103+
Assert.IsNull(info.Result);
104+
Assert.IsTrue(info.Args.Handled);
75105
}
76106
}
77107
}

0 commit comments

Comments
 (0)