@@ -10,11 +10,12 @@ namespace Rubberduck.SmartIndenter
10
10
internal class AbsoluteCodeLine
11
11
{
12
12
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 ) ) ;
16
17
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 ) ;
18
19
private static readonly Regex ProcedureStartRegex = new Regex ( @"^(Public\s|Private\s|Friend\s)?(Static\s)?(Sub|Function|Property\s(Let|Get|Set))\s" ) ;
19
20
private static readonly Regex ProcedureStartIgnoreRegex = new Regex ( @"^[LR]?Set\s|^Let\s|^(Public|Private)\sDeclare\s(Function|Sub)" ) ;
20
21
private static readonly Regex ProcedureEndRegex = new Regex ( @"^End\s(Sub|Function|Property)" ) ;
@@ -31,13 +32,17 @@ internal class AbsoluteCodeLine
31
32
private uint _lineNumber ;
32
33
private bool _numbered ;
33
34
private string _code ;
34
- private bool _stupidLineEnding ;
35
+ private readonly bool _stupidLineEnding ;
35
36
private readonly string [ ] _segments ;
36
37
private List < string > _strings ;
38
+ private List < string > _brackets ;
37
39
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 )
39
43
{
40
44
_settings = settings ;
45
+ Previous = previous ;
41
46
42
47
if ( code . EndsWith ( StupidLineEnding ) )
43
48
{
@@ -51,38 +56,85 @@ public AbsoluteCodeLine(string code, IIndenterSettings settings)
51
56
52
57
Original = code ;
53
58
54
- ExtractStringLiterals ( ) ;
59
+ ExtractStringLiteralsAndBrackets ( ) ;
55
60
ExtractLineNumber ( ) ;
56
61
ExtractEndOfLineComment ( ) ;
57
62
63
+ _code = Regex . Replace ( _code , StringPlaceholder + "+" , StringPlaceholder . ToString ( CultureInfo . InvariantCulture ) ) ;
64
+ _code = Regex . Replace ( _code , BracketPlaceholder + "+" , BracketPlaceholder . ToString ( CultureInfo . InvariantCulture ) ) . Trim ( ) ;
58
65
_segments = _code . Split ( new [ ] { ": " } , StringSplitOptions . None ) ;
59
66
}
60
67
61
- private void ExtractStringLiterals ( )
68
+ //TODO: This should be a class.
69
+ private void ExtractStringLiteralsAndBrackets ( )
62
70
{
63
71
_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 ++ )
67
81
{
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
+ }
69
121
}
70
- _code = StringLiteralRegex . Replace ( _code , StringPlaceholder ) ;
122
+ _code = new string ( chars ) ;
71
123
}
72
124
73
125
private void ExtractLineNumber ( )
74
126
{
75
- var match = LineNumberRegex . Match ( _code ) ;
76
- if ( match . Success )
127
+ if ( Previous == null || ! Previous . HasContinuation )
77
128
{
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
+ }
85
136
}
137
+ _code = _code . Trim ( ) ;
86
138
}
87
139
88
140
private void ExtractEndOfLineComment ( )
@@ -97,8 +149,27 @@ private void ExtractEndOfLineComment()
97
149
EndOfLineComment = match . Groups [ "comment" ] . Value . Trim ( ) ;
98
150
}
99
151
152
+ public AbsoluteCodeLine Previous { get ; private set ; }
153
+
100
154
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
+
102
173
public string EndOfLineComment { get ; private set ; }
103
174
104
175
public IEnumerable < string > Segments
@@ -141,12 +212,12 @@ public bool HasDeclarationContinuation
141
212
142
213
public bool HasContinuation
143
214
{
144
- get { return _code . EndsWith ( " _" ) || EndOfLineComment . EndsWith ( " _" ) ; }
215
+ get { return _code . Equals ( "_" ) || _code . EndsWith ( " _" ) || EndOfLineComment . EndsWith ( " _" ) ; }
145
216
}
146
217
147
218
public bool IsPrecompilerDirective
148
219
{
149
- get { return Original . TrimStart ( ) . StartsWith ( "#" ) ; }
220
+ get { return _code . TrimStart ( ) . StartsWith ( "#" ) ; }
150
221
}
151
222
152
223
public bool IsBareDebugStatement
@@ -248,6 +319,10 @@ public string Indent(int indents, bool atProcStart, bool absolute = false)
248
319
{
249
320
code = _strings . Aggregate ( code , ( current , literal ) => StringReplaceRegex . Replace ( current , literal , 1 ) ) ;
250
321
}
322
+ if ( _brackets . Any ( ) )
323
+ {
324
+ code = _brackets . Aggregate ( code , ( current , expr ) => BracketReplaceRegex . Replace ( current , expr , 1 ) ) ;
325
+ }
251
326
252
327
code = string . Join ( string . Empty , number , new string ( ' ' , gap ) , code ) ;
253
328
if ( string . IsNullOrEmpty ( EndOfLineComment ) )
@@ -283,10 +358,20 @@ public override string ToString()
283
358
}
284
359
285
360
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
+ }
287
367
var alignTokens = _segments [ 0 ] . Split ( new [ ] { " As " } , StringSplitOptions . None ) ;
368
+ if ( alignTokens . Length <= 1 )
369
+ {
370
+ return ;
371
+ }
288
372
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 ) ) ) ;
290
375
}
291
376
}
292
377
}
0 commit comments