Skip to content

Commit df4ccec

Browse files
authored
Merge pull request #2400 from comintern/next
Multi-line Dim fix for Indenter
2 parents aed17f4 + e699016 commit df4ccec

File tree

4 files changed

+194
-86
lines changed

4 files changed

+194
-86
lines changed

Rubberduck.SmartIndenter/AbsoluteCodeLine.cs

Lines changed: 45 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ namespace Rubberduck.SmartIndenter
99
{
1010
internal class AbsoluteCodeLine
1111
{
12+
private const string StupidLineEnding = ": _";
1213
private const string StringPlaceholder = "\a";
1314
private static readonly Regex StringLiteralRegex = new Regex("\"(?:[^\"]+|\"\")*\"");
1415
private static readonly Regex StringReplaceRegex = new Regex(StringPlaceholder);
@@ -21,7 +22,7 @@ internal class AbsoluteCodeLine
2122
private static readonly Regex TypeEnumEndRegex = new Regex(@"^End\s(Enum|Type)");
2223
private static readonly Regex InProcedureInRegex = new Regex(@"^(Else)?If\s.*\sThen$|^Else$|^Case\s|^With|^For\s|^Do$|^Do\s|^While$|^While\s|^Select Case");
2324
private static readonly Regex InProcedureOutRegex = new Regex(@"^Else(If)?|^Case\s|^End With|^Next\s|^Next$|^Loop$|^Loop\s|^Wend$|^End If$|^End Select");
24-
private static readonly Regex DeclarationRegex = new Regex(@"^(Dim|Const|Static|Public|Private)\s.*\sAs\s");
25+
private static readonly Regex DeclarationRegex = new Regex(@"^(Dim|Const|Static|Public|Private)\s(.*(\sAs\s)?|_)");
2526
private static readonly Regex PrecompilerInRegex = new Regex(@"^#(Else)?If\s.+Then$|^#Else$");
2627
private static readonly Regex PrecompilerOutRegex = new Regex(@"^#ElseIf\s.+Then|^#Else$|#End\sIf$");
2728
private static readonly Regex SingleLineElseIfRegex = new Regex(@"^ElseIf\s.*\sThen\s.*");
@@ -30,13 +31,24 @@ internal class AbsoluteCodeLine
3031
private uint _lineNumber;
3132
private bool _numbered;
3233
private string _code;
34+
private bool _stupidLineEnding;
3335
private readonly string[] _segments;
3436
private List<string> _strings;
3537

3638
public AbsoluteCodeLine(string code, IIndenterSettings settings)
3739
{
3840
_settings = settings;
39-
_code = code;
41+
42+
if (code.EndsWith(StupidLineEnding))
43+
{
44+
_code = code.Substring(0, code.Length - StupidLineEnding.Length);
45+
_stupidLineEnding = true;
46+
}
47+
else
48+
{
49+
_code = code;
50+
}
51+
4052
Original = code;
4153

4254
ExtractStringLiterals();
@@ -110,7 +122,21 @@ public bool ContainsOnlyComment
110122

111123
public bool IsDeclaration
112124
{
113-
get { return !IsEmpty && DeclarationRegex.IsMatch(_code); }
125+
get { return !IsEmpty && (!IsProcedureStart && !ProcedureStartIgnoreRegex.IsMatch(_code)) && DeclarationRegex.IsMatch(_code); }
126+
}
127+
128+
public bool IsDeclarationContinuation { get; set; }
129+
130+
public bool HasDeclarationContinuation
131+
{
132+
get
133+
{
134+
return (!IsProcedureStart && !ProcedureStartIgnoreRegex.IsMatch(_code)) &&
135+
!ContainsOnlyComment &&
136+
string.IsNullOrEmpty(EndOfLineComment) &&
137+
HasContinuation &&
138+
((IsDeclarationContinuation && Segments.Count() == 1) || DeclarationRegex.IsMatch(Segments.Last()));
139+
}
114140
}
115141

116142
public bool HasContinuation
@@ -205,14 +231,17 @@ public string Indent(int indents, bool atProcStart, bool absolute = false)
205231
if ((IsPrecompilerDirective && _settings.ForceCompilerDirectivesInColumn1) ||
206232
(IsBareDebugStatement && _settings.ForceDebugStatementsInColumn1) ||
207233
(atProcStart && !_settings.IndentFirstCommentBlock && ContainsOnlyComment) ||
208-
(atProcStart && !_settings.IndentFirstDeclarationBlock && IsDeclaration))
234+
(atProcStart && !_settings.IndentFirstDeclarationBlock && (IsDeclaration || IsDeclarationContinuation)))
209235
{
210236
indents = 0;
211237
}
212238

213239
var number = _numbered ? _lineNumber.ToString(CultureInfo.InvariantCulture) : string.Empty;
214240
var gap = Math.Max((absolute ? indents : _settings.IndentSpaces * indents) - number.Length, number.Length > 0 ? 1 : 0);
215-
AlignDims(gap);
241+
if (_settings.AlignDims && (IsDeclaration || IsDeclarationContinuation))
242+
{
243+
AlignDims(gap);
244+
}
216245

217246
var code = string.Join(": ", _segments);
218247
if (_strings.Any())
@@ -223,22 +252,26 @@ public string Indent(int indents, bool atProcStart, bool absolute = false)
223252
code = string.Join(string.Empty, number, new string(' ', gap), code);
224253
if (string.IsNullOrEmpty(EndOfLineComment))
225254
{
226-
return code;
255+
return code + (_stupidLineEnding ? StupidLineEnding : string.Empty);
227256
}
228257

229258
var position = Original.LastIndexOf(EndOfLineComment, StringComparison.Ordinal);
230259
switch (_settings.EndOfLineCommentStyle)
231260
{
232261
case EndOfLineCommentStyle.Absolute:
233-
return string.Format("{0}{1}{2}", code, new string(' ', Math.Max(position - code.Length, 1)), EndOfLineComment);
262+
return string.Format("{0}{1}{2}{3}", code, new string(' ', Math.Max(position - code.Length, 1)),
263+
EndOfLineComment, _stupidLineEnding ? StupidLineEnding : string.Empty);
234264
case EndOfLineCommentStyle.SameGap:
235265
var uncommented = Original.Substring(0, position - 1);
236-
return string.Format("{0}{1}{2}", code, new string(' ', uncommented.Length - uncommented.TrimEnd().Length + 1), EndOfLineComment);
266+
return string.Format("{0}{1}{2}{3}", code, new string(' ', uncommented.Length - uncommented.TrimEnd().Length + 1),
267+
EndOfLineComment, _stupidLineEnding ? StupidLineEnding : string.Empty);
237268
case EndOfLineCommentStyle.StandardGap:
238-
return string.Format("{0}{1}{2}", code, new string(' ', _settings.IndentSpaces * 2), EndOfLineComment);
269+
return string.Format("{0}{1}{2}{3}", code, new string(' ', _settings.IndentSpaces * 2), EndOfLineComment,
270+
_stupidLineEnding ? StupidLineEnding : string.Empty);
239271
case EndOfLineCommentStyle.AlignInColumn:
240272
var align = _settings.EndOfLineCommentColumnSpaceAlignment - code.Length;
241-
return string.Format("{0}{1}{2}", code, new string(' ', Math.Max(align - 1, 1)), EndOfLineComment);
273+
return string.Format("{0}{1}{2}{3}", code, new string(' ', Math.Max(align - 1, 1)), EndOfLineComment,
274+
_stupidLineEnding ? StupidLineEnding : string.Empty);
242275
default:
243276
throw new InvalidEnumArgumentException();
244277
}
@@ -250,13 +283,10 @@ public override string ToString()
250283
}
251284

252285
private void AlignDims(int postition)
253-
{
254-
if (!DeclarationRegex.IsMatch(_segments[0]) || IsProcedureStart) return;
286+
{
255287
var alignTokens = _segments[0].Split(new[] { " As " }, StringSplitOptions.None);
256288
var gap = Math.Max(_settings.AlignDimColumn - postition - alignTokens[0].Length - 2, 0);
257-
_segments[0] = string.Format("{0}{1} As {2}", alignTokens[0].Trim(),
258-
(!_settings.AlignDims) ? string.Empty : new string(' ', gap),
259-
string.Join(" As ", alignTokens.Skip(1)));
289+
_segments[0] = string.Format("{0}{1} As {2}", alignTokens[0].Trim(), new string(' ', gap), string.Join(" As ", alignTokens.Skip(1)));
260290
}
261291
}
262292
}

Rubberduck.SmartIndenter/LogicalCodeLine.cs

Lines changed: 18 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,8 @@ public LogicalCodeLine(AbsoluteCodeLine first, IIndenterSettings settings)
2828

2929
public void AddContinuationLine(AbsoluteCodeLine line)
3030
{
31+
var last = _lines.Last();
32+
line.IsDeclarationContinuation = last.HasDeclarationContinuation && !line.ContainsOnlyComment;
3133
_lines.Add(line);
3234
}
3335

@@ -46,7 +48,16 @@ public int EnumTypeIndents
4648
{
4749
get
4850
{
49-
return _settings.IndentEnumTypeAsProcedure && AtEnumTypeStart && IsCommentBlock && !_settings.IndentFirstCommentBlock ? 0 : 1;
51+
if (!IsEnumOrTypeMember)
52+
{
53+
return 0;
54+
}
55+
return _settings.IndentEnumTypeAsProcedure &&
56+
AtEnumTypeStart &&
57+
IsCommentBlock &&
58+
!_settings.IndentFirstCommentBlock
59+
? 0
60+
: 1;
5061
}
5162
}
5263

@@ -95,7 +106,7 @@ public bool IsEnumOrTypeEnd
95106

96107
public bool IsDeclaration
97108
{
98-
get { return _lines.All(x => x.IsDeclaration); }
109+
get { return _lines.All(x => x.IsDeclaration || x.IsDeclarationContinuation); }
99110
}
100111

101112
public bool IsCommentBlock
@@ -125,6 +136,11 @@ public string Indented()
125136

126137
foreach (var line in _lines.Skip(1))
127138
{
139+
if (line.IsDeclarationContinuation && !line.IsProcedureStart)
140+
{
141+
output.Add(line.Indent(IndentationLevel, AtProcedureStart));
142+
continue;
143+
}
128144
if (line.ContainsOnlyComment)
129145
{
130146
commentPos = alignment;

RubberduckTests/SmartIndenter/LineContinuationTests.cs

Lines changed: 7 additions & 68 deletions
Original file line numberDiff line numberDiff line change
@@ -515,76 +515,16 @@ public void ContinuationsInProcedureDeclarationsWorks()
515515
"Sub MySub()",
516516
" Dim x1 As Integer",
517517
" Dim _",
518-
" x2 _",
519-
" As Integer",
520-
" Dim x3 As _",
521-
" Integer",
522-
" Dim x4 _",
523-
" As _",
524-
" Integer",
525-
" Dim x5 As Integer: _",
526-
" Dim x6 As _",
527-
" Integer",
528-
" Dim x7 As Integer _",
529-
" 'Comment _",
530-
" as _",
531-
" integer",
532-
"End Sub"
533-
};
534-
535-
var indenter = new Indenter(null, () =>
536-
{
537-
var s = IndenterSettingsTests.GetMockIndenterSettings();
538-
s.AlignCommentsWithCode = true;
539-
s.IndentFirstDeclarationBlock = true;
540-
return s;
541-
});
542-
var actual = indenter.Indent(code, string.Empty);
543-
Assert.IsTrue(expected.SequenceEqual(actual));
544-
}
545-
546-
//https://github.com/rubberduck-vba/Rubberduck/issues/1287
547-
[TestMethod] // Broken in VB6 SmartIndenter.
548-
[TestCategory("Indenter")]
549-
public void ContinuationsInProcedureDeclarationsNoCommentAlignWorks()
550-
{
551-
var code = new[]
552-
{
553-
"Sub MySub()",
554-
"Dim x1 As Integer",
555-
"Dim _",
556-
"x2 _",
557-
"As Integer",
558-
"Dim x3 As _",
559-
"Integer",
560-
"Dim x4 _",
561-
"As _",
562-
"Integer",
563-
"Dim x5 As Integer: _",
564-
"Dim x6 As _",
565-
"Integer",
566-
"Dim x7 As Integer _",
567-
"'Comment _",
568-
"as _",
569-
"integer",
570-
"End Sub"
571-
};
572-
573-
var expected = new[]
574-
{
575-
"Sub MySub()",
576-
" Dim x1 As Integer",
577-
" Dim _",
578-
" x2 _",
579-
" As Integer",
518+
" x2 _",
519+
" As Integer",
580520
" Dim x3 As _",
581-
" Integer",
521+
" Integer",
582522
" Dim x4 _",
583-
" As _",
584-
" Integer",
523+
" As _",
524+
" Integer",
585525
" Dim x5 As Integer: _",
586-
" Dim x6 As _",
587-
" Integer",
526+
" Dim x6 As _",
527+
" Integer",
588528
" Dim x7 As Integer _",
589529
" 'Comment _",
590530
" as _",
@@ -595,7 +535,6 @@ public void ContinuationsInProcedureDeclarationsNoCommentAlignWorks()
595535
var indenter = new Indenter(null, () =>
596536
{
597537
var s = IndenterSettingsTests.GetMockIndenterSettings();
598-
s.AlignCommentsWithCode = false;
599538
s.IndentFirstDeclarationBlock = true;
600539
return s;
601540
});

0 commit comments

Comments
 (0)