Skip to content

Commit ccc4a72

Browse files
committed
Fixed infinite backreferenced bug in string escaping, added bracketed expression support, misc indenter fixes.
1 parent 6f253fa commit ccc4a72

File tree

6 files changed

+339
-27
lines changed

6 files changed

+339
-27
lines changed

Rubberduck.SmartIndenter/AbsoluteCodeLine.cs

Lines changed: 98 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -10,11 +10,12 @@ namespace Rubberduck.SmartIndenter
1010
internal class AbsoluteCodeLine
1111
{
1212
private const string StupidLineEnding = ": _";
13-
private const string StringPlaceholder = "\a";
14-
private static readonly Regex StringLiteralRegex = new Regex("\"(?:[^\"]+|\"\")*\"");
15-
private static readonly Regex StringReplaceRegex = new Regex(StringPlaceholder);
13+
private const char StringPlaceholder = '\a';
14+
private const char BracketPlaceholder = '\x2';
15+
private static readonly Regex StringReplaceRegex = new Regex(StringPlaceholder.ToString(CultureInfo.InvariantCulture));
16+
private static readonly Regex BracketReplaceRegex = new Regex(BracketPlaceholder.ToString(CultureInfo.InvariantCulture));
1617
private static readonly Regex LineNumberRegex = new Regex(@"^(?<number>\d+)\s+(?<code>.*)", RegexOptions.ExplicitCapture);
17-
private static readonly Regex EndOfLineCommentRegex = new Regex(@"^(?!(Rem\s)|('))(?<code>.*)(\s(?<comment>'.*))$", RegexOptions.ExplicitCapture);
18+
private static readonly Regex EndOfLineCommentRegex = new Regex(@"^(?!(Rem\s)|('))(?<code>[^']*)(\s(?<comment>'.*))$", RegexOptions.ExplicitCapture);
1819
private static readonly Regex ProcedureStartRegex = new Regex(@"^(Public\s|Private\s|Friend\s)?(Static\s)?(Sub|Function|Property\s(Let|Get|Set))\s");
1920
private static readonly Regex ProcedureStartIgnoreRegex = new Regex(@"^[LR]?Set\s|^Let\s|^(Public|Private)\sDeclare\s(Function|Sub)");
2021
private static readonly Regex ProcedureEndRegex = new Regex(@"^End\s(Sub|Function|Property)");
@@ -31,9 +32,10 @@ internal class AbsoluteCodeLine
3132
private uint _lineNumber;
3233
private bool _numbered;
3334
private string _code;
34-
private bool _stupidLineEnding;
35+
private readonly bool _stupidLineEnding;
3536
private readonly string[] _segments;
3637
private List<string> _strings;
38+
private List<string> _brackets;
3739

3840
public AbsoluteCodeLine(string code, IIndenterSettings settings)
3941
{
@@ -51,23 +53,69 @@ public AbsoluteCodeLine(string code, IIndenterSettings settings)
5153

5254
Original = code;
5355

54-
ExtractStringLiterals();
56+
ExtractStringLiteralsAndBrackets();
5557
ExtractLineNumber();
5658
ExtractEndOfLineComment();
57-
59+
_code = Regex.Replace(_code, StringPlaceholder + "+", StringPlaceholder.ToString(CultureInfo.InvariantCulture));
60+
_code = Regex.Replace(_code, BracketPlaceholder + "+", BracketPlaceholder.ToString(CultureInfo.InvariantCulture)).Trim();
5861
_segments = _code.Split(new[] { ": " }, StringSplitOptions.None);
5962
}
6063

61-
private void ExtractStringLiterals()
64+
//TODO: This should be a class.
65+
private void ExtractStringLiteralsAndBrackets()
6266
{
6367
_strings = new List<string>();
64-
var matches = StringLiteralRegex.Matches(_code);
65-
if (matches.Count == 0) return;
66-
foreach (var match in matches)
68+
_brackets = new List<string>();
69+
70+
var chars = _code.ToCharArray();
71+
var quoted = false;
72+
var bracketed = false;
73+
var ins = 0;
74+
var strpos = 0;
75+
var brkpos = 0;
76+
for (var c = 0; c < chars.Length; c++)
6777
{
68-
_strings.Add(match.ToString());
78+
if (chars[c] == '"' && !bracketed)
79+
{
80+
if (!quoted)
81+
{
82+
strpos = c;
83+
quoted = true;
84+
continue;
85+
}
86+
if (c + 1 < chars.Length && chars[c] == '"')
87+
{
88+
c++;
89+
}
90+
quoted = false;
91+
_strings.Add(new string(chars.Skip(strpos).Take(c - strpos).ToArray()));
92+
for (var e = strpos; e < c; e++)
93+
{
94+
chars[e] = StringPlaceholder;
95+
}
96+
}
97+
else if (!quoted && !bracketed && chars[c] == '[')
98+
{
99+
bracketed = true;
100+
brkpos = c;
101+
ins++;
102+
}
103+
else if (!quoted && bracketed && chars[c] == ']')
104+
{
105+
ins--;
106+
if (ins != 0)
107+
{
108+
continue;
109+
}
110+
bracketed = false;
111+
_brackets.Add(new string(chars.Skip(brkpos).Take(c - brkpos).ToArray()));
112+
for (var e = brkpos; e < c; e++)
113+
{
114+
chars[e] = BracketPlaceholder;
115+
}
116+
}
69117
}
70-
_code = StringLiteralRegex.Replace(_code, StringPlaceholder);
118+
_code = new string(chars);
71119
}
72120

73121
private void ExtractLineNumber()
@@ -77,12 +125,9 @@ private void ExtractLineNumber()
77125
{
78126
_numbered = true;
79127
_lineNumber = Convert.ToUInt32(match.Groups["number"].Value);
80-
_code = match.Groups["code"].Value.Trim();
81-
}
82-
else
83-
{
84-
_code = _code.Trim();
128+
_code = match.Groups["code"].Value;
85129
}
130+
_code = _code.Trim();
86131
}
87132

88133
private void ExtractEndOfLineComment()
@@ -98,7 +143,24 @@ private void ExtractEndOfLineComment()
98143
}
99144

100145
public string Original { get; private set; }
101-
146+
147+
public string Escaped
148+
{
149+
get
150+
{
151+
var output = Original;
152+
foreach (var item in _strings)
153+
{
154+
output = output.Replace(item, new string(StringPlaceholder, item.Length));
155+
}
156+
foreach (var item in _brackets)
157+
{
158+
output = output.Replace(item, new string(BracketPlaceholder, item.Length));
159+
}
160+
return output;
161+
}
162+
}
163+
102164
public string EndOfLineComment { get; private set; }
103165

104166
public IEnumerable<string> Segments
@@ -146,7 +208,7 @@ public bool HasContinuation
146208

147209
public bool IsPrecompilerDirective
148210
{
149-
get { return Original.TrimStart().StartsWith("#"); }
211+
get { return _code.TrimStart().StartsWith("#"); }
150212
}
151213

152214
public bool IsBareDebugStatement
@@ -248,6 +310,10 @@ public string Indent(int indents, bool atProcStart, bool absolute = false)
248310
{
249311
code = _strings.Aggregate(code, (current, literal) => StringReplaceRegex.Replace(current, literal, 1));
250312
}
313+
if (_brackets.Any())
314+
{
315+
code = _brackets.Aggregate(code, (current, expr) => BracketReplaceRegex.Replace(current, expr, 1));
316+
}
251317

252318
code = string.Join(string.Empty, number, new string(' ', gap), code);
253319
if (string.IsNullOrEmpty(EndOfLineComment))
@@ -283,10 +349,20 @@ public override string ToString()
283349
}
284350

285351
private void AlignDims(int postition)
286-
{
352+
{
353+
if (_segments[0].Trim().StartsWith("As "))
354+
{
355+
_segments[0] = string.Format("{0}{1}", new String(' ', _settings.AlignDimColumn - postition - 1), _segments[0].Trim());
356+
return;
357+
}
287358
var alignTokens = _segments[0].Split(new[] { " As " }, StringSplitOptions.None);
359+
if (alignTokens.Length <= 1)
360+
{
361+
return;
362+
}
288363
var gap = Math.Max(_settings.AlignDimColumn - postition - alignTokens[0].Length - 2, 0);
289-
_segments[0] = string.Format("{0}{1} As {2}", alignTokens[0].Trim(), new string(' ', gap), string.Join(" As ", alignTokens.Skip(1)));
364+
_segments[0] = string.Format("{0}{1} As {2}", alignTokens[0].Trim(), new string(' ', gap),
365+
string.Join(" As ", alignTokens.Skip(1)));
290366
}
291367
}
292368
}

Rubberduck.SmartIndenter/LogicalCodeLine.cs

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -132,7 +132,7 @@ public string Indented()
132132
var current = _lines.First().Indent(IndentationLevel, AtProcedureStart);
133133
var commentPos = string.IsNullOrEmpty(_lines.First().EndOfLineComment) ? 0 : current.Length - _lines.First().EndOfLineComment.Length;
134134
output.Add(current);
135-
var alignment = FunctionAlign(current, _lines[1].Original.Trim().StartsWith(":="));
135+
var alignment = FunctionAlign(current, _lines[1].Escaped.Trim().StartsWith(":="));
136136

137137
//foreach (var line in _lines.Skip(1))
138138
for (var i = 1; i < _lines.Count; i++)
@@ -156,7 +156,7 @@ public string Indented()
156156
var operatorAdjust = _settings.IgnoreOperatorsInContinuations && OperatorIgnoreRegex.IsMatch(line.Original) ? 2 : 0;
157157
current = line.Indent(Math.Max(alignment - operatorAdjust, 0), AtProcedureStart, true);
158158
output.Add(current);
159-
alignment = FunctionAlign(current, i + 1 < _lines.Count && _lines[i + 1].Original.Trim().StartsWith(":="));
159+
alignment = FunctionAlign(current, i + 1 < _lines.Count && _lines[i + 1].Escaped.Trim().StartsWith(":="));
160160
commentPos = string.IsNullOrEmpty(line.EndOfLineComment) ? 0 : current.Length - line.EndOfLineComment.Length;
161161
}
162162

@@ -181,9 +181,11 @@ private int FunctionAlign(string line, bool splitNamed)
181181
var character = line.Substring(index - 1, 1);
182182
switch (character)
183183
{
184-
case "\"":
185-
//A String => jump to the end of it
186-
while (!line.Substring(index++, 1).Equals("\"")) { }
184+
case "\a":
185+
while (!line.Substring(index++, 1).Equals("\a")) { }
186+
break;
187+
case "\x2":
188+
while (!line.Substring(index++, 1).Equals("\x2")) { }
187189
break;
188190
case "(":
189191
//Start of another function => remember this position

RubberduckTests/Inspections/ParameterCanBeByValInspectionTests.cs

Lines changed: 47 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -953,6 +953,7 @@ Sub Foo(ByRef _
953953
Assert.AreEqual(expectedCode, module.Content());
954954
}
955955

956+
//https://github.com/rubberduck-vba/Rubberduck/issues/2408
956957
[TestMethod]
957958
[TestCategory("Inspections")]
958959
public void ParameterCanBeByVal_QuickFixWithOptionalWorks()
@@ -986,6 +987,7 @@ Debug.Print foo
986987
Assert.AreEqual(expectedCode, module.Content());
987988
}
988989

990+
//https://github.com/rubberduck-vba/Rubberduck/issues/2408
989991
[TestMethod]
990992
[TestCategory("Inspections")]
991993
public void ParameterCanBeByVal_QuickFixWithOptionalByRefWorks()
@@ -1019,6 +1021,51 @@ Debug.Print foo
10191021
Assert.AreEqual(expectedCode, module.Content());
10201022
}
10211023

1024+
//https://github.com/rubberduck-vba/Rubberduck/issues/2408
1025+
[TestMethod]
1026+
[TestCategory("Inspections")]
1027+
public void ParameterCanBeByVal_QuickFixWithOptional_LineContinuationsWorks()
1028+
{
1029+
Assert.Inconclusive("Pending more comprehensive fix.");
1030+
const string inputCode =
1031+
@"Sub foo(Optional _
1032+
ByRef _
1033+
foo _
1034+
As _
1035+
Byte _
1036+
)
1037+
Debug.Print foo
1038+
End Sub";
1039+
1040+
const string expectedCode =
1041+
@"Sub foo(Optional _
1042+
ByVal _
1043+
foo _
1044+
As _
1045+
Byte _
1046+
)
1047+
Debug.Print foo
1048+
End Sub";
1049+
1050+
//Arrange
1051+
var builder = new MockVbeBuilder();
1052+
IVBComponent component;
1053+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
1054+
var project = vbe.Object.VBProjects[0];
1055+
var module = project.VBComponents[0].CodeModule;
1056+
var mockHost = new Mock<IHostApplication>();
1057+
mockHost.SetupAllProperties();
1058+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
1059+
1060+
parser.Parse(new CancellationTokenSource());
1061+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
1062+
1063+
var inspection = new ParameterCanBeByValInspection(parser.State);
1064+
inspection.GetInspectionResults().First().QuickFixes.Single(s => s is PassParameterByValueQuickFix).Fix();
1065+
1066+
Assert.AreEqual(expectedCode, module.Content());
1067+
}
1068+
10221069
[TestMethod]
10231070
[TestCategory("Inspections")]
10241071
public void InspectionType()

RubberduckTests/SmartIndenter/LineContinuationTests.cs

Lines changed: 83 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -542,7 +542,90 @@ public void ContinuationsInProcedureDeclarationsWorks()
542542
Assert.IsTrue(expected.SequenceEqual(actual));
543543
}
544544

545+
//https://github.com/rubberduck-vba/Rubberduck/issues/2407
546+
[TestMethod]
547+
[TestCategory("Indenter")]
548+
public void ContinuationsInProcedureDeclarationsWithAlignWorks()
549+
{
550+
var code = new[]
551+
{
552+
"Sub MySub()",
553+
"Dim x1 As Integer, x2 _",
554+
"As Integer",
555+
"End Sub"
556+
};
557+
558+
var expected = new[]
559+
{
560+
"Sub MySub()",
561+
" Dim x1 As Integer, x2 _",
562+
" As Integer",
563+
"End Sub"
564+
};
565+
566+
var indenter = new Indenter(null, () =>
567+
{
568+
var s = IndenterSettingsTests.GetMockIndenterSettings();
569+
s.IndentFirstDeclarationBlock = true;
570+
s.AlignDims = true;
571+
s.AlignDimColumn = 15;
572+
return s;
573+
});
574+
var actual = indenter.Indent(code, string.Empty);
575+
Assert.IsTrue(expected.SequenceEqual(actual));
576+
}
577+
578+
//https://github.com/rubberduck-vba/Rubberduck/issues/2407
579+
[TestMethod]
580+
[TestCategory("Indenter")]
581+
public void ContinuationsInProcedureDeclarationsWithAlignWorksBareType()
582+
{
583+
var code = new[]
584+
{
585+
"Sub MySub()",
586+
"Dim x1 As Integer",
587+
"Dim x2 As _",
588+
"Integer",
589+
"Dim x3 As Integer: _",
590+
"Dim x4 As _",
591+
"Integer",
592+
"Dim x5 As Integer _",
593+
"'Comment _",
594+
"as _",
595+
"integer",
596+
"End Sub"
597+
};
598+
599+
var expected = new[]
600+
{
601+
"Sub MySub()",
602+
" Dim x1 As Integer",
603+
" Dim x2 As _",
604+
" Integer",
605+
" Dim x3 As Integer: _",
606+
" Dim x4 As _",
607+
" Integer",
608+
" Dim x5 As Integer _",
609+
" 'Comment _",
610+
" as _",
611+
" integer",
612+
"End Sub"
613+
};
614+
615+
var indenter = new Indenter(null, () =>
616+
{
617+
var s = IndenterSettingsTests.GetMockIndenterSettings();
618+
s.IndentFirstDeclarationBlock = true;
619+
s.AlignDims = true;
620+
s.AlignDimColumn = 15;
621+
return s;
622+
});
623+
var actual = indenter.Indent(code, string.Empty);
624+
Assert.IsTrue(expected.SequenceEqual(actual));
625+
}
626+
545627
[TestMethod]
628+
[TestCategory("Indenter")]
546629
public void ContinuationWithOnlyCommentWorks()
547630
{
548631
var code = new[]

0 commit comments

Comments
 (0)