Skip to content

Commit aaeaecb

Browse files
committed
Merge branch 'next' of https://github.com/rubberduck-vba/Rubberduck into next
2 parents 83bb063 + b49c6c9 commit aaeaecb

File tree

10 files changed

+637
-45
lines changed

10 files changed

+637
-45
lines changed

RetailCoder.VBE/Inspections/ChangeParameterByRefByValQuickFix.cs

Lines changed: 32 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
1+
using System;
12
using Antlr4.Runtime;
3+
using Rubberduck.Parsing.Grammar;
24
using Rubberduck.VBEditor;
35

46
namespace Rubberduck.Inspections
@@ -15,16 +17,38 @@ public ChangeParameterByRefByValQuickFix(ParserRuleContext context, QualifiedSel
1517

1618
public override void Fix()
1719
{
18-
var parameter = Context.GetText();
19-
var newContent = string.Concat(_newToken, " ", parameter);
20-
var selection = Selection.Selection;
21-
22-
var module = Selection.QualifiedName.Component.CodeModule;
20+
try
2321
{
24-
var lines = module.GetLines(selection.StartLine, selection.LineCount);
25-
var result = lines.Replace(parameter, newContent);
26-
module.ReplaceLine(selection.StartLine, result);
22+
dynamic context = Context;
23+
var parameter = Context.GetText();
24+
dynamic args = Context.parent;
25+
var argList = args.GetText();
26+
var module = Selection.QualifiedName.Component.CodeModule;
27+
{
28+
string result;
29+
if (context.OPTIONAL() != null)
30+
{
31+
result = parameter.Replace(Tokens.Optional, Tokens.Optional + ' ' + _newToken);
32+
}
33+
else
34+
{
35+
result = _newToken + ' ' + parameter;
36+
}
37+
38+
dynamic proc = args.parent;
39+
var startLine = proc.GetType().GetProperty("Start").GetValue(proc).Line;
40+
var stopLine = proc.GetType().GetProperty("Stop").GetValue(proc).Line;
41+
var code = module.GetLines(startLine, stopLine - startLine + 1);
42+
result = code.Replace(argList, argList.Replace(parameter, result));
43+
44+
foreach (var line in result.Split(new[] {"\r\n"}, StringSplitOptions.None))
45+
{
46+
module.ReplaceLine(startLine++, line);
47+
}
48+
}
2749
}
50+
// ReSharper disable once EmptyGeneralCatchClause
51+
catch { }
2852
}
2953
}
3054
}

RetailCoder.VBE/Inspections/PassParameterByValueQuickFix.cs

Lines changed: 33 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
using System;
12
using System.Linq;
23
using Antlr4.Runtime;
34
using Rubberduck.Common;
@@ -73,14 +74,42 @@ private void FixMethods()
7374

7475
private void FixMethod(VBAParser.ArgContext context, QualifiedSelection qualifiedSelection)
7576
{
76-
var selectionLength = context.BYREF() == null ? 0 : 6;
77+
var parameter = context.GetText();
78+
var argList = context.parent.GetText();
7779

7880
var module = qualifiedSelection.QualifiedName.Component.CodeModule;
7981
{
80-
var lines = module.GetLines(context.Start.Line, 1);
82+
string result;
83+
if (context.BYREF() != null)
84+
{
85+
result = parameter.Replace(Tokens.ByRef, Tokens.ByVal);
86+
}
87+
else if (context.OPTIONAL() != null)
88+
{
89+
result = parameter.Replace(Tokens.Optional, Tokens.Optional + ' ' + Tokens.ByVal);
90+
}
91+
else
92+
{
93+
result = Tokens.ByVal + ' ' + parameter;
94+
}
8195

82-
var result = lines.Remove(context.Start.Column, selectionLength).Insert(context.Start.Column, Tokens.ByVal + ' ');
83-
module.ReplaceLine(context.Start.Line, result);
96+
var startLine = 0;
97+
var stopLine = 0;
98+
try
99+
{
100+
dynamic proc = context.parent.parent;
101+
startLine = proc.GetType().GetProperty("Start").GetValue(proc).Line;
102+
stopLine = proc.GetType().GetProperty("Stop").GetValue(proc).Line;
103+
}
104+
catch { return; }
105+
106+
var code = module.GetLines(startLine, stopLine - startLine + 1);
107+
result = code.Replace(argList, argList.Replace(parameter, result));
108+
109+
foreach (var line in result.Split(new[] { "\r\n" }, StringSplitOptions.None))
110+
{
111+
module.ReplaceLine(startLine++, line);
112+
}
84113
}
85114
}
86115
}

Rubberduck.SmartIndenter/AbsoluteCodeLine.cs

Lines changed: 112 additions & 27 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,13 +32,17 @@ 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

38-
public AbsoluteCodeLine(string code, IIndenterSettings settings)
40+
public AbsoluteCodeLine(string code, IIndenterSettings settings) : this(code, settings, null) { }
41+
42+
public AbsoluteCodeLine(string code, IIndenterSettings settings, AbsoluteCodeLine previous)
3943
{
4044
_settings = settings;
45+
Previous = previous;
4146

4247
if (code.EndsWith(StupidLineEnding))
4348
{
@@ -51,38 +56,85 @@ public AbsoluteCodeLine(string code, IIndenterSettings settings)
5156

5257
Original = code;
5358

54-
ExtractStringLiterals();
59+
ExtractStringLiteralsAndBrackets();
5560
ExtractLineNumber();
5661
ExtractEndOfLineComment();
5762

63+
_code = Regex.Replace(_code, StringPlaceholder + "+", StringPlaceholder.ToString(CultureInfo.InvariantCulture));
64+
_code = Regex.Replace(_code, BracketPlaceholder + "+", BracketPlaceholder.ToString(CultureInfo.InvariantCulture)).Trim();
5865
_segments = _code.Split(new[] { ": " }, StringSplitOptions.None);
5966
}
6067

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

73125
private void ExtractLineNumber()
74126
{
75-
var match = LineNumberRegex.Match(_code);
76-
if (match.Success)
127+
if (Previous == null || !Previous.HasContinuation)
77128
{
78-
_numbered = true;
79-
_lineNumber = Convert.ToUInt32(match.Groups["number"].Value);
80-
_code = match.Groups["code"].Value.Trim();
81-
}
82-
else
83-
{
84-
_code = _code.Trim();
129+
var match = LineNumberRegex.Match(_code);
130+
if (match.Success)
131+
{
132+
_numbered = true;
133+
_lineNumber = Convert.ToUInt32(match.Groups["number"].Value);
134+
_code = match.Groups["code"].Value;
135+
}
85136
}
137+
_code = _code.Trim();
86138
}
87139

88140
private void ExtractEndOfLineComment()
@@ -97,8 +149,27 @@ private void ExtractEndOfLineComment()
97149
EndOfLineComment = match.Groups["comment"].Value.Trim();
98150
}
99151

152+
public AbsoluteCodeLine Previous { get; private set; }
153+
100154
public string Original { get; private set; }
101-
155+
156+
public string Escaped
157+
{
158+
get
159+
{
160+
var output = Original;
161+
foreach (var item in _strings)
162+
{
163+
output = output.Replace(item, new string(StringPlaceholder, item.Length));
164+
}
165+
foreach (var item in _brackets)
166+
{
167+
output = output.Replace(item, new string(BracketPlaceholder, item.Length));
168+
}
169+
return output;
170+
}
171+
}
172+
102173
public string EndOfLineComment { get; private set; }
103174

104175
public IEnumerable<string> Segments
@@ -141,12 +212,12 @@ public bool HasDeclarationContinuation
141212

142213
public bool HasContinuation
143214
{
144-
get { return _code.EndsWith(" _") || EndOfLineComment.EndsWith(" _"); }
215+
get { return _code.Equals("_") || _code.EndsWith(" _") || EndOfLineComment.EndsWith(" _"); }
145216
}
146217

147218
public bool IsPrecompilerDirective
148219
{
149-
get { return Original.TrimStart().StartsWith("#"); }
220+
get { return _code.TrimStart().StartsWith("#"); }
150221
}
151222

152223
public bool IsBareDebugStatement
@@ -248,6 +319,10 @@ public string Indent(int indents, bool atProcStart, bool absolute = false)
248319
{
249320
code = _strings.Aggregate(code, (current, literal) => StringReplaceRegex.Replace(current, literal, 1));
250321
}
322+
if (_brackets.Any())
323+
{
324+
code = _brackets.Aggregate(code, (current, expr) => BracketReplaceRegex.Replace(current, expr, 1));
325+
}
251326

252327
code = string.Join(string.Empty, number, new string(' ', gap), code);
253328
if (string.IsNullOrEmpty(EndOfLineComment))
@@ -283,10 +358,20 @@ public override string ToString()
283358
}
284359

285360
private void AlignDims(int postition)
286-
{
361+
{
362+
if (_segments[0].Trim().StartsWith("As "))
363+
{
364+
_segments[0] = string.Format("{0}{1}", new String(' ', _settings.AlignDimColumn - postition - 1), _segments[0].Trim());
365+
return;
366+
}
287367
var alignTokens = _segments[0].Split(new[] { " As " }, StringSplitOptions.None);
368+
if (alignTokens.Length <= 1)
369+
{
370+
return;
371+
}
288372
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)));
373+
_segments[0] = string.Format("{0}{1} As {2}", alignTokens[0].Trim(), new string(' ', gap),
374+
string.Join(" As ", alignTokens.Skip(1)));
290375
}
291376
}
292377
}

Rubberduck.SmartIndenter/Indenter.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -107,10 +107,11 @@ private IEnumerable<LogicalCodeLine> BuildLogicalCodeLines(IEnumerable<string> l
107107
var settings = _settings.Invoke();
108108
var logical = new List<LogicalCodeLine>();
109109
LogicalCodeLine current = null;
110+
AbsoluteCodeLine previous = null;
110111

111112
foreach (var line in lines)
112113
{
113-
var absolute = new AbsoluteCodeLine(line, settings);
114+
var absolute = new AbsoluteCodeLine(line, settings, previous);
114115
if (current == null)
115116
{
116117
current = new LogicalCodeLine(absolute, settings);
@@ -125,6 +126,7 @@ private IEnumerable<LogicalCodeLine> BuildLogicalCodeLines(IEnumerable<string> l
125126
{
126127
current = null;
127128
}
129+
previous = absolute;
128130
}
129131
return logical;
130132
}

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

0 commit comments

Comments
 (0)