Skip to content

Commit 0a52a91

Browse files
committed
added failing tests (ignored for now)
1 parent 5bceeb7 commit 0a52a91

File tree

2 files changed

+93
-52
lines changed

2 files changed

+93
-52
lines changed

Rubberduck.Core/AutoComplete/Service/SelfClosingPairCompletionService.cs

Lines changed: 68 additions & 52 deletions
Original file line numberDiff line numberDiff line change
@@ -166,7 +166,7 @@ private CodeString DeleteMatchingTokensMultiline(SelfClosingPair pair, CodeStrin
166166
var closingLine = lines[closingTokenPosition.EndLine].Remove(closingTokenPosition.StartColumn, 1);
167167
lines[closingTokenPosition.EndLine] = closingLine;
168168

169-
if (closingLine == pair.OpeningChar.ToString())
169+
if (closingLine == pair.OpeningChar.ToString() || closingLine == pair.OpeningChar + " _" || closingLine == pair.OpeningChar + " & _")
170170
{
171171
lines[closingTokenPosition.EndLine] = string.Empty;
172172
}
@@ -184,78 +184,94 @@ private CodeString DeleteMatchingTokensMultiline(SelfClosingPair pair, CodeStrin
184184
lines = lines.Where((x, i) => i <= position.StartLine || !string.IsNullOrWhiteSpace(x)).ToArray();
185185
lastLine = lines[lines.Length - 1];
186186

187-
if (lastLine.EndsWith(" _"))
187+
if (lastLine.EndsWith(" _") && finalCaretPosition.StartLine == lines.Length - 1)
188188
{
189-
// we can't leave the logical line ending with a line continuation token.
190-
if (lastLine.EndsWith(" & vbNewLine & _"))
191-
{
192-
// assume " & vbNewLine & _" was added by smart-concat?
193-
lines[lines.Length - 1] = lastLine.Substring(0,
194-
lastLine.Length - " & vbNewLine & _".Length);
195-
}
196-
else
197-
{
198-
lines[lines.Length - 1] = lastLine.TrimEnd(' ', '_');
199-
}
189+
finalCaretPosition = HandleBackspaceContinuations(lines, finalCaretPosition);
200190
}
191+
}
192+
193+
var caretLine = lines[finalCaretPosition.StartLine];
194+
if (caretLine.EndsWith(" _") && finalCaretPosition.StartLine == lines.Length - 1)
195+
{
196+
finalCaretPosition = HandleBackspaceContinuations(lines, finalCaretPosition);
197+
}
198+
else if (caretLine.EndsWith("& _") || caretLine.EndsWith("& _"))
199+
{
200+
HandleBackspaceContinuations(lines, finalCaretPosition);
201+
}
201202

202-
var nonEmptyLines = lines
203-
.Where(x => !string.IsNullOrWhiteSpace(x))
204-
.ToArray();
205-
var lastNonEmptyLine = nonEmptyLines.Length > 0 ? nonEmptyLines[nonEmptyLines.Length - 1] : null;
206-
if (lastNonEmptyLine != null)
203+
var nonEmptyLines = lines.Where(x => !string.IsNullOrWhiteSpace(x)).ToArray();
204+
var lastNonEmptyLine = nonEmptyLines.Length > 0 ? nonEmptyLines[nonEmptyLines.Length - 1] : null;
205+
if (lastNonEmptyLine != null)
206+
{
207+
if (position.StartLine > nonEmptyLines.Length - 1)
207208
{
208-
if (position.StartLine > nonEmptyLines.Length - 1)
209-
{
210-
// caret is on a now-empty line, shift one line up.
211-
finalCaretPosition = new Selection(position.StartLine - 1, lastNonEmptyLine.Length - 1);
212-
}
209+
// caret is on a now-empty line, shift one line up.
210+
finalCaretPosition = new Selection(position.StartLine - 1, lastNonEmptyLine.Length - 1);
211+
}
213212

214-
if (lastNonEmptyLine.EndsWith(" _"))
213+
if (lastNonEmptyLine.EndsWith(" _"))
214+
{
215+
var newPosition = HandleBackspaceContinuations(nonEmptyLines, new Selection(nonEmptyLines.Length - 1, 1));
216+
if (finalCaretPosition.StartLine == nonEmptyLines.Length - 1)
215217
{
216-
nonEmptyLines[nonEmptyLines.Length - 1] = lastNonEmptyLine.Remove(lastNonEmptyLine.Length - 2);
217-
lastNonEmptyLine = nonEmptyLines[nonEmptyLines.Length - 1];
218-
219-
if (lastNonEmptyLine.EndsWith("&"))
220-
{
221-
// we're not concatenating anything anymore; remove concat operator too.
222-
var concatOffset = lastNonEmptyLine.EndsWith(" &") ? 2 : 1;
223-
nonEmptyLines[nonEmptyLines.Length - 1] = lastNonEmptyLine.Remove(lastNonEmptyLine.Length - concatOffset);
224-
TrimLastNonEmptyLine(nonEmptyLines, "& vbNewLine");
225-
TrimLastNonEmptyLine(nonEmptyLines, "& vbCrLf");
226-
TrimLastNonEmptyLine(nonEmptyLines, "& vbCr");
227-
TrimLastNonEmptyLine(nonEmptyLines, "& vbLf");
228-
}
229-
230-
// we're keeping the closing quote, but let's put the caret inside:
231-
lastNonEmptyLine = nonEmptyLines[nonEmptyLines.Length - 1];
232-
var quoteOffset = lastNonEmptyLine.EndsWith("\"") ? 1 : 0;
233-
finalCaretPosition = new Selection(
234-
finalCaretPosition.StartLine,
235-
lastNonEmptyLine.Length - quoteOffset);
218+
finalCaretPosition = newPosition;
236219
}
237-
238-
lines = nonEmptyLines;
239220
}
221+
222+
lines = nonEmptyLines;
240223
}
241224

225+
242226
// remove any dangling empty lines...
243-
//lines = lines.Where((x, i) => i <= position.StartLine || !string.IsNullOrWhiteSpace(x)).ToArray();
227+
lines = lines.Where((x, i) => i <= position.StartLine || !string.IsNullOrWhiteSpace(x)).ToArray();
244228

245229
return new CodeString(string.Join("\r\n", lines), finalCaretPosition,
246230
new Selection(original.SnippetPosition.StartLine, 1, original.SnippetPosition.EndLine, 1));
231+
}
232+
233+
private static Selection HandleBackspaceContinuations(string[] nonEmptyLines, Selection finalCaretPosition)
234+
{
235+
var lineIndex = Math.Min(finalCaretPosition.StartLine, nonEmptyLines.Length - 1);
236+
var line = nonEmptyLines[lineIndex];
237+
if (line.EndsWith(" _") && lineIndex == nonEmptyLines.Length - 1)
238+
{
239+
nonEmptyLines[lineIndex] = line.Remove(line.Length - 2);
240+
line = nonEmptyLines[lineIndex];
241+
}
247242

243+
if (lineIndex == nonEmptyLines.Length - 1)
244+
{
245+
line = nonEmptyLines[lineIndex];
246+
}
247+
248+
if (line.EndsWith("&"))
249+
{
250+
// we're not concatenating anything anymore; remove concat operator too.
251+
var concatOffset = line.EndsWith(" &") ? 2 : 1;
252+
nonEmptyLines[lineIndex] = line.Remove(line.Length - concatOffset);
253+
}
254+
TrimNonEmptyLine(nonEmptyLines, lineIndex, "& vbNewLine");
255+
TrimNonEmptyLine(nonEmptyLines, lineIndex, "& vbCrLf");
256+
TrimNonEmptyLine(nonEmptyLines, lineIndex, "& vbCr");
257+
TrimNonEmptyLine(nonEmptyLines, lineIndex, "& vbLf");
258+
259+
// we're keeping the closing quote, but let's put the caret inside:
260+
line = nonEmptyLines[lineIndex];
261+
var quoteOffset = line.EndsWith("\"") ? 1 : 0;
262+
finalCaretPosition = new Selection(finalCaretPosition.StartLine, line.Length - quoteOffset);
263+
return finalCaretPosition;
248264
}
249265

250-
private static void TrimLastNonEmptyLine(string[] nonEmptyLines, string ending)
266+
private static void TrimNonEmptyLine(string[] nonEmptyLines, int lineIndex, string ending)
251267
{
252-
var lastNonEmptyLine = nonEmptyLines[nonEmptyLines.Length - 1];
253-
if (lastNonEmptyLine.EndsWith(ending, StringComparison.OrdinalIgnoreCase))
268+
var line = nonEmptyLines[lineIndex];
269+
if (line.EndsWith(ending, StringComparison.OrdinalIgnoreCase))
254270
{
255-
var offset = lastNonEmptyLine.EndsWith(" " + ending, StringComparison.OrdinalIgnoreCase)
271+
var offset = line.EndsWith(" " + ending, StringComparison.OrdinalIgnoreCase)
256272
? ending.Length + 1
257273
: ending.Length;
258-
nonEmptyLines[nonEmptyLines.Length - 1] = lastNonEmptyLine.Remove(lastNonEmptyLine.Length - offset);
274+
nonEmptyLines[lineIndex] = line.Remove(line.Length - offset);
259275
}
260276
}
261277

RubberduckTests/AutoComplete/SelfClosingPairCompletionTests.cs

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -221,6 +221,31 @@ public void WhenCaretBetweenOpeningAndClosingChars_BackspaceRemovesBoth()
221221
Assert.AreEqual(expected, result);
222222
}
223223

224+
[Test][Ignore("todo: figure out how to make this pass without breaking something else.")]
225+
public void BackspacingWorksWhenCaretIsNotOnLastNonEmptyLine_ConcatOnSameLine()
226+
{
227+
var pair = new SelfClosingPair('"', '"');
228+
var input = Keys.Back;
229+
var original = "foo = \"\" & _\r\n \"\" & _\r\n \"|\" & _\r\n \"\"".ToCodeString();
230+
var expected = "foo = \"\" & _\r\n \"|\" & _\r\n \"\"".ToCodeString();
231+
232+
var result = Run(pair, original, input);
233+
Assert.AreEqual(expected, result);
234+
}
235+
236+
[Test]
237+
[Ignore("todo: figure out how to make this pass without breaking something else.")]
238+
public void BackspacingWorksWhenCaretIsNotOnLastNonEmptyLine_ConcatOnNextLine()
239+
{
240+
var pair = new SelfClosingPair('"', '"');
241+
var input = Keys.Back;
242+
var original = "foo = \"\" _\r\n & \"\" _\r\n & \"|\" _\r\n & \"\"".ToCodeString();
243+
var expected = "foo = \"\" _\r\n & \"|\" _\r\n & \"\"".ToCodeString();
244+
245+
var result = Run(pair, original, input);
246+
Assert.AreEqual(expected, result);
247+
}
248+
224249
[Test]
225250
public void WhenBackspacingClearsLineContinuatedCaretLine_PlacesCaretInsideStringOnPreviousLine()
226251
{

0 commit comments

Comments
 (0)