@@ -89,8 +89,7 @@ private CodeString HandleClosingChar(SelfClosingPair pair, CodeString original)
89
89
90
90
var nextIsClosingChar = original . CaretLine . Length > original . CaretCharIndex &&
91
91
original . CaretLine [ original . CaretCharIndex ] == pair . ClosingChar ;
92
-
93
- if ( pair . IsSymetric && nextIsClosingChar )
92
+ if ( nextIsClosingChar )
94
93
{
95
94
var nextPosition = original . CaretPosition . ShiftRight ( ) ;
96
95
var newCode = original . Code ;
@@ -113,6 +112,7 @@ private CodeString DeleteMatchingTokens(SelfClosingPair pair, CodeString origina
113
112
var line = lines [ original . CaretPosition . StartLine ] ;
114
113
if ( line . Length == 0 )
115
114
{
115
+ // nothing to delete at caret position... bail out.
116
116
return null ;
117
117
}
118
118
@@ -122,70 +122,125 @@ private CodeString DeleteMatchingTokens(SelfClosingPair pair, CodeString origina
122
122
var previousChar = line [ previous ] ;
123
123
var nextChar = line [ next ] ;
124
124
125
- if ( original . CaretPosition . EndColumn < next && previousChar == pair . OpeningChar && nextChar == pair . ClosingChar )
125
+ if ( original . CaretPosition . StartColumn < next &&
126
+ previousChar == pair . OpeningChar &&
127
+ nextChar == pair . ClosingChar )
126
128
{
127
129
if ( line . Length == 2 )
128
130
{
129
- // entire line consists in the self-closing pair itself
131
+ // entire line consists in the self-closing pair itself.
130
132
return new CodeString ( string . Empty , default , Selection . Empty . ShiftRight ( ) ) ;
131
133
}
132
- else
133
- {
134
- lines [ original . CaretPosition . StartLine ] = line . Remove ( previous , 2 ) ;
135
- return new CodeString ( string . Join ( "\r \n " , lines ) , original . CaretPosition . ShiftLeft ( ) , original . SnippetPosition ) ;
136
- }
134
+
135
+ // simple case; caret is between the opening and closing chars - remove both.
136
+ lines [ original . CaretPosition . StartLine ] = line . Remove ( previous , 2 ) ;
137
+ return new CodeString ( string . Join ( "\r \n " , lines ) , original . CaretPosition . ShiftLeft ( ) , original . SnippetPosition ) ;
137
138
}
138
139
139
140
if ( previous < line . Length - 1 && previousChar == pair . OpeningChar )
140
141
{
141
- Selection closingTokenPosition ;
142
- closingTokenPosition = line [ Math . Min ( line . Length - 1 , next ) ] == pair . ClosingChar
143
- ? position
144
- : FindMatchingTokenPosition ( pair , original ) ;
145
-
146
- if ( closingTokenPosition != default )
147
- {
148
- var closingLine = lines [ closingTokenPosition . EndLine ] . Remove ( closingTokenPosition . StartColumn , 1 ) ;
149
- lines [ closingTokenPosition . EndLine ] = closingLine ;
142
+ return DeleteMatchingTokensMultiline ( pair , original ) ;
143
+ }
150
144
151
- if ( closingLine == pair . OpeningChar . ToString ( ) )
145
+ return null ;
146
+ }
147
+
148
+ private CodeString DeleteMatchingTokensMultiline ( SelfClosingPair pair , CodeString original )
149
+ {
150
+ var position = original . CaretPosition ;
151
+ var lines = original . Lines ;
152
+ var line = lines [ original . CaretPosition . StartLine ] ;
153
+ var next = Math . Min ( line . Length - 1 , position . StartColumn ) ;
154
+
155
+ Selection closingTokenPosition ;
156
+ closingTokenPosition = line [ Math . Min ( line . Length - 1 , next ) ] == pair . ClosingChar
157
+ ? position
158
+ : FindMatchingTokenPosition ( pair , original ) ;
159
+
160
+ if ( closingTokenPosition == default )
161
+ {
162
+ // could not locate the closing token... bail out.
163
+ return null ;
164
+ }
165
+
166
+ var closingLine = lines [ closingTokenPosition . EndLine ] . Remove ( closingTokenPosition . StartColumn , 1 ) ;
167
+ lines [ closingTokenPosition . EndLine ] = closingLine ;
168
+
169
+ if ( closingLine == pair . OpeningChar . ToString ( ) )
170
+ {
171
+ lines [ closingTokenPosition . EndLine ] = string . Empty ;
172
+ }
173
+ else
174
+ {
175
+ var openingLine = lines [ position . StartLine ] . Remove ( position . ShiftLeft ( ) . StartColumn , 1 ) ;
176
+ lines [ position . StartLine ] = openingLine ;
177
+ }
178
+
179
+ var finalCaretPosition = original . CaretPosition . ShiftLeft ( ) ;
180
+
181
+ var lastLine = lines [ lines . Length - 1 ] ;
182
+ if ( string . IsNullOrEmpty ( lastLine . Trim ( ) ) )
183
+ {
184
+ lines = lines . Where ( ( x , i ) => i <= position . StartLine || ! string . IsNullOrWhiteSpace ( x ) ) . ToArray ( ) ;
185
+ lastLine = lines [ lines . Length - 1 ] ;
186
+
187
+ if ( lastLine . EndsWith ( " _" ) )
188
+ {
189
+ // we can't leave the logical line ending with a line continuation token.
190
+ if ( lastLine . EndsWith ( " & vbNewLine & _" ) )
152
191
{
153
- lines [ closingTokenPosition . EndLine ] = string . Empty ;
192
+ // assume " & vbNewLine & _" was added by smart-concat?
193
+ lines [ lines . Length - 1 ] = lastLine . Substring ( 0 ,
194
+ lastLine . Length - " & vbNewLine & _" . Length ) ;
154
195
}
155
196
else
156
197
{
157
- var openingLine = lines [ position . StartLine ] . Remove ( position . ShiftLeft ( ) . StartColumn , 1 ) ;
158
- lines [ position . StartLine ] = openingLine ;
198
+ lines [ lines . Length - 1 ] = lastLine . TrimEnd ( ' ' , '_' ) ;
159
199
}
200
+ }
160
201
161
- var finalCaretPosition = original . CaretPosition . ShiftLeft ( ) ;
162
- lines = lines . Where ( ( x , i ) => i <= finalCaretPosition . StartLine || ! string . IsNullOrWhiteSpace ( x ) ) . ToArray ( ) ;
163
- if ( lines [ lines . Length - 1 ] . EndsWith ( " _" ) )
202
+ var nonEmptyLines = lines
203
+ . Where ( x => ! string . IsNullOrWhiteSpace ( x ) )
204
+ . ToArray ( ) ;
205
+ var lastNonEmptyLine = nonEmptyLines . Length > 0 ? nonEmptyLines [ nonEmptyLines . Length - 1 ] : null ;
206
+ if ( lastNonEmptyLine != null )
207
+ {
208
+ if ( position . StartLine > nonEmptyLines . Length - 1 )
164
209
{
165
- // logical line can't end with a line continuation token.. .
166
- lines [ lines . Length - 1 ] = lines [ lines . Length - 1 ] . TrimEnd ( ' ' , '_' ) ;
210
+ // caret is on a now-empty line, shift one line up .
211
+ finalCaretPosition = new Selection ( position . StartLine - 1 , lastNonEmptyLine . Length - 1 ) ;
167
212
}
168
213
169
- if ( position . StartLine >= 1 &&
170
- string . IsNullOrWhiteSpace ( lines [ position . StartLine ] . Trim ( ) ) &&
171
- lines [ position . StartLine - 1 ] . EndsWith ( " & _" ) &&
172
- position . StartLine == lines . Length - 1 )
214
+ if ( lastNonEmptyLine . EndsWith ( " _" ) )
173
215
{
174
-
175
- lines [ position . StartLine - 1 ] = lines [ position . StartLine - 1 ]
176
- . Remove ( lines [ position . StartLine - 1 ] . Length - 4 ) ;
177
- var quoteOffset = lines [ position . StartLine - 1 ] . EndsWith ( "\" " ) ? 1 : 0 ;
178
- finalCaretPosition = new Selection ( finalCaretPosition . StartLine - 1 , lines [ position . StartLine - 1 ] . Length - quoteOffset ) ;
216
+ nonEmptyLines [ nonEmptyLines . Length - 1 ] = lastNonEmptyLine . Remove ( lastNonEmptyLine . Length - 2 ) ;
217
+ lastNonEmptyLine = nonEmptyLines [ nonEmptyLines . Length - 1 ] ;
218
+
219
+ if ( lastNonEmptyLine . EndsWith ( "&" ) )
220
+ {
221
+ // we're not concatenating anything anymore; remove concat operator too.
222
+ var concatOffset = lastNonEmptyLine . EndsWith ( " &" ) ? 2 : 1 ;
223
+ nonEmptyLines [ nonEmptyLines . Length - 1 ] = lastNonEmptyLine . Remove ( lastNonEmptyLine . Length - concatOffset ) ;
224
+ lastNonEmptyLine = nonEmptyLines [ nonEmptyLines . Length - 1 ] ;
225
+ }
226
+
227
+ // we're keeping the closing quote, but let's put the caret inside:
228
+ var quoteOffset = lastNonEmptyLine . EndsWith ( "\" " ) ? 1 : 0 ;
229
+ finalCaretPosition = new Selection (
230
+ finalCaretPosition . StartLine ,
231
+ lastNonEmptyLine . Length - quoteOffset ) ;
179
232
}
180
233
181
- lines = lines . Where ( ( x , i ) => i <= finalCaretPosition . StartLine || ! string . IsNullOrWhiteSpace ( x ) ) . ToArray ( ) ;
182
-
183
- return new CodeString ( string . Join ( "\r \n " , lines ) , finalCaretPosition ,
184
- new Selection ( original . SnippetPosition . StartLine , 1 , original . SnippetPosition . EndLine , 1 ) ) ;
234
+ lines = nonEmptyLines ;
185
235
}
186
236
}
187
237
188
- return null ;
238
+ // remove any dangling empty lines...
239
+ //lines = lines.Where((x, i) => i <= position.StartLine || !string.IsNullOrWhiteSpace(x)).ToArray();
240
+
241
+ return new CodeString ( string . Join ( "\r \n " , lines ) , finalCaretPosition ,
242
+ new Selection ( original . SnippetPosition . StartLine , 1 , original . SnippetPosition . EndLine , 1 ) ) ;
243
+
189
244
}
190
245
191
246
private Selection FindMatchingTokenPosition ( SelfClosingPair pair , CodeString original )
0 commit comments