Skip to content

Commit 8e102f7

Browse files
committed
adjust spacing before first procedure, adjust tests to meet new assumption. closes #3942
1 parent 5f7837b commit 8e102f7

File tree

6 files changed

+209
-7
lines changed

6 files changed

+209
-7
lines changed

Rubberduck.SmartIndenter/Indenter.cs

Lines changed: 56 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -65,7 +65,14 @@ public void IndentCurrentModule()
6565
{
6666
return;
6767
}
68-
Indent(pane.CodeModule.Parent);
68+
69+
using (var module = pane.CodeModule)
70+
{
71+
using (var component = module.Parent)
72+
{
73+
Indent(component);
74+
}
75+
}
6976
}
7077
}
7178

@@ -245,12 +252,30 @@ private IEnumerable<string> GenerateCodeLineStrings(IEnumerable<LogicalCodeLine>
245252

246253
List<LogicalCodeLine> indent;
247254
if (!procedure && settings.VerticallySpaceProcedures)
248-
{
255+
{
249256
indent = new List<LogicalCodeLine>();
250257
var lines = logical.ToArray();
258+
var header = true;
259+
var inEnumType = false;
251260
for (var i = 0; i < lines.Length; i++)
252261
{
253262
indent.Add(lines[i]);
263+
264+
if (header && lines[i].IsEnumOrTypeStart)
265+
{
266+
inEnumType = true;
267+
}
268+
if (header && lines[i].IsEnumOrTypeEnd)
269+
{
270+
inEnumType = false;
271+
}
272+
273+
if (header && !inEnumType && lines[i].IsProcedureStart)
274+
{
275+
header = false;
276+
SpaceHeader(indent, settings);
277+
continue;
278+
}
254279
if (!lines[i].IsEnumOrTypeEnd && !lines[i].IsProcudureEnd)
255280
{
256281
continue;
@@ -264,7 +289,7 @@ private IEnumerable<string> GenerateCodeLineStrings(IEnumerable<LogicalCodeLine>
264289
}
265290
indent.Add(lines[i]);
266291
}
267-
else if (i == lines.Length && forceTrailingNewLines)
292+
else if (forceTrailingNewLines && i == lines.Length)
268293
{
269294
indent.Add(new LogicalCodeLine(Enumerable.Repeat(new AbsoluteCodeLine(string.Empty, settings), Math.Max(settings.LinesBetweenProcedures, 1)), settings));
270295
}
@@ -281,5 +306,33 @@ private IEnumerable<string> GenerateCodeLineStrings(IEnumerable<LogicalCodeLine>
281306
}
282307
return output;
283308
}
309+
310+
private static void SpaceHeader(IList<LogicalCodeLine> header, IIndenterSettings settings)
311+
{
312+
var commentSkipped = false;
313+
var commentLines = 0;
314+
for (var i = header.Count - 2; i >= 0; i--)
315+
{
316+
if (!commentSkipped && header[i].IsCommentBlock)
317+
{
318+
commentLines++;
319+
continue;
320+
}
321+
322+
commentSkipped = true;
323+
if (header[i].IsEmpty)
324+
{
325+
header.RemoveAt(i);
326+
}
327+
else
328+
{
329+
header.Insert(header.Count - 1 - commentLines,
330+
new LogicalCodeLine(
331+
Enumerable.Repeat(new AbsoluteCodeLine(string.Empty, settings),
332+
settings.LinesBetweenProcedures), settings));
333+
return;
334+
}
335+
}
336+
}
284337
}
285338
}

Rubberduck.SmartIndenter/LogicalCodeLine.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -181,7 +181,7 @@ public override string ToString()
181181

182182
private static readonly Regex StartIgnoreRegex = new Regex(@"^(\d*\s)?\s*[LR]?Set\s|^(\d*\s)?\s*Let\s|^(\d*\s)?\s*(Public|Private)\sDeclare\s(Function|Sub)|^(\d*\s+)", RegexOptions.IgnoreCase);
183183
private readonly Stack<AlignmentToken> _alignment = new Stack<AlignmentToken>();
184-
private int _nestingDepth = 0;
184+
private int _nestingDepth;
185185

186186
//The splitNamed parameter is a straight up hack for fixing https://github.com/rubberduck-vba/Rubberduck/issues/2402
187187
private int FunctionAlign(string line, bool splitNamed)

RubberduckTests/Commands/IndentCommandTests.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -110,6 +110,7 @@ End Sub
110110

111111
var expected =
112112
@"Option Explicit ' at least I used it...
113+
113114
Sub InverseIndent()
114115
Dim d As Boolean
115116
Dim s As Integer

RubberduckTests/SmartIndenter/EndOfLineCommentTests.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -219,6 +219,7 @@ public void WorksOutsideOfProcedures()
219219
var expected = new[]
220220
{
221221
"#Const Foo = Bar 'Comment",
222+
"",
222223
"Private Sub Test()",
223224
"End Sub"
224225
};

RubberduckTests/SmartIndenter/MiscAndCornerCaseTests.cs

Lines changed: 39 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System.Linq;
22
using NUnit.Framework;
33
using Rubberduck.SmartIndenter;
4+
using Rubberduck.UI.Command;
45
using RubberduckTests.Settings;
56

67
namespace RubberduckTests.SmartIndenter
@@ -899,8 +900,7 @@ public void ElseWithEndingColonWorks()
899900
var actual = indenter.Indent(code);
900901
Assert.IsTrue(expected.SequenceEqual(actual));
901902
}
902-
903-
903+
904904
[Test]
905905
[Category("Indenter")]
906906
public void ElseWithTrailingSegmentWorks()
@@ -929,5 +929,42 @@ public void ElseWithTrailingSegmentWorks()
929929
var actual = indenter.Indent(code);
930930
Assert.IsTrue(expected.SequenceEqual(actual));
931931
}
932+
933+
//failing test for https://github.com/rubberduck-vba/Rubberduck/issues/3210
934+
[Test]
935+
[Ignore("Most likely requires the parse tree.")]
936+
[Category("Indenter")]
937+
public void LineNumbersInsideContinuationsWork()
938+
{
939+
var code = new[]
940+
{
941+
"Sub Foo()",
942+
" _",
943+
"10",
944+
" _",
945+
"foo _",
946+
": Beep",
947+
"",
948+
"20 bar: Beep",
949+
"End Sub"
950+
};
951+
952+
var expected = new[]
953+
{
954+
"Sub Foo()",
955+
" _",
956+
"10",
957+
" _",
958+
"foo _",
959+
": Beep",
960+
"",
961+
"20 bar: Beep",
962+
"End Sub"
963+
};
964+
965+
var indenter = new Indenter(null, () => IndenterSettingsTests.GetMockIndenterSettings());
966+
var actual = indenter.Indent(code);
967+
Assert.IsTrue(expected.SequenceEqual(actual));
968+
}
932969
}
933970
}

RubberduckTests/SmartIndenter/VerticalSpacingTests.cs

Lines changed: 111 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@
33
using Rubberduck.SmartIndenter;
44
using Rubberduck.UI.Command;
55
using Rubberduck.VBEditor;
6-
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
76
using RubberduckTests.Mocks;
87
using RubberduckTests.Settings;
98

@@ -595,5 +594,116 @@ Private Sub TestThree()
595594
Assert.AreEqual(expected, component.CodeModule.Content());
596595
}
597596
}
597+
598+
[Test]
599+
[Category("Indenter")]
600+
public void VerticalSpacing_MaintainsSpacingAboveFirstProcedure()
601+
{
602+
var code = new[]
603+
{
604+
@"Option Explicit",
605+
"Function TestFunction() As Long",
606+
"End Function",
607+
"Sub TestSub()",
608+
"End Sub"
609+
};
610+
611+
var expected = new[]
612+
{
613+
@"Option Explicit",
614+
"",
615+
"Function TestFunction() As Long",
616+
"End Function",
617+
"",
618+
"Sub TestSub()",
619+
"End Sub"
620+
};
621+
622+
var indenter = new Indenter(null, () =>
623+
{
624+
var s = IndenterSettingsTests.GetMockIndenterSettings();
625+
s.VerticallySpaceProcedures = true;
626+
s.LinesBetweenProcedures = 1;
627+
return s;
628+
});
629+
var actual = indenter.Indent(code);
630+
Assert.IsTrue(expected.SequenceEqual(actual));
631+
}
632+
633+
[Test]
634+
[Category("Indenter")]
635+
public void VerticalSpacing_MaintainsIgnoresCommentAboveFirstProcedure()
636+
{
637+
var code = new[]
638+
{
639+
@"Option Explicit",
640+
"'Comment",
641+
"Function TestFunction() As Long",
642+
"End Function",
643+
"Sub TestSub()",
644+
"End Sub"
645+
};
646+
647+
var expected = new[]
648+
{
649+
@"Option Explicit",
650+
"",
651+
"'Comment",
652+
"Function TestFunction() As Long",
653+
"End Function",
654+
"",
655+
"Sub TestSub()",
656+
"End Sub"
657+
};
658+
659+
var indenter = new Indenter(null, () =>
660+
{
661+
var s = IndenterSettingsTests.GetMockIndenterSettings();
662+
s.VerticallySpaceProcedures = true;
663+
s.LinesBetweenProcedures = 1;
664+
return s;
665+
});
666+
var actual = indenter.Indent(code);
667+
Assert.IsTrue(expected.SequenceEqual(actual));
668+
}
669+
670+
[Test]
671+
[Category("Indenter")]
672+
public void VerticalSpacing_RemovesExtraSpacingAboveFirstProcedure()
673+
{
674+
var code = new[]
675+
{
676+
@"Option Explicit",
677+
"",
678+
"",
679+
"",
680+
"",
681+
"Function TestFunction() As Long",
682+
"End Function",
683+
"Sub TestSub()",
684+
"End Sub"
685+
};
686+
687+
var expected = new[]
688+
{
689+
@"Option Explicit",
690+
"",
691+
"Function TestFunction() As Long",
692+
"End Function",
693+
"",
694+
"Sub TestSub()",
695+
"End Sub"
696+
};
697+
698+
var indenter = new Indenter(null, () =>
699+
{
700+
var s = IndenterSettingsTests.GetMockIndenterSettings();
701+
s.VerticallySpaceProcedures = true;
702+
s.LinesBetweenProcedures = 1;
703+
return s;
704+
});
705+
var actual = indenter.Indent(code);
706+
Assert.IsTrue(expected.SequenceEqual(actual));
707+
}
598708
}
599709
}

0 commit comments

Comments
 (0)