@@ -11,7 +11,6 @@ public interface IUnreachableCaseInspector
11
11
{
12
12
void InspectForUnreachableCases ( ) ;
13
13
string SelectExpressionTypeName { get ; }
14
- Func < string , ParserRuleContext , string > GetVariableDeclarationTypeName { set ; get ; }
15
14
List < ParserRuleContext > UnreachableCases { get ; }
16
15
List < ParserRuleContext > InherentlyUnreachableCases { get ; }
17
16
List < ParserRuleContext > MismatchTypeCases { get ; }
@@ -24,23 +23,22 @@ public class UnreachableCaseInspector : IUnreachableCaseInspector
24
23
private readonly IEnumerable < VBAParser . CaseClauseContext > _caseClauses ;
25
24
private readonly ParserRuleContext _caseElseContext ;
26
25
private readonly IParseTreeValueFactory _valueFactory ;
26
+ private readonly Func < string , ParserRuleContext , string > _getVariableDeclarationTypeName ;
27
27
private IParseTreeValue _selectExpressionValue ;
28
28
29
29
public UnreachableCaseInspector ( VBAParser . SelectCaseStmtContext selectCaseContext ,
30
30
IParseTreeVisitorResults inspValues ,
31
31
IParseTreeValueFactory valueFactory ,
32
- Func < string , ParserRuleContext , string > GetVariableTypeName = null )
32
+ Func < string , ParserRuleContext , string > getVariableTypeName = null )
33
33
{
34
34
_valueFactory = valueFactory ;
35
35
_caseClauses = selectCaseContext . caseClause ( ) ;
36
36
_caseElseContext = selectCaseContext . caseElseClause ( ) ;
37
- GetVariableDeclarationTypeName = GetVariableTypeName ;
37
+ _getVariableDeclarationTypeName = getVariableTypeName ;
38
38
ParseTreeValueResults = inspValues ;
39
- SetSelectExpressionTypeName ( selectCaseContext as ParserRuleContext , inspValues ) ;
39
+ SetSelectExpressionTypeName ( selectCaseContext , inspValues ) ;
40
40
}
41
41
42
- public Func < string , ParserRuleContext , string > GetVariableDeclarationTypeName { set ; get ; }
43
-
44
42
public List < ParserRuleContext > UnreachableCases { set ; get ; } = new List < ParserRuleContext > ( ) ;
45
43
46
44
public List < ParserRuleContext > MismatchTypeCases { set ; get ; } = new List < ParserRuleContext > ( ) ;
@@ -53,7 +51,7 @@ public UnreachableCaseInspector(VBAParser.SelectCaseStmtContext selectCaseContex
53
51
54
52
public string SelectExpressionTypeName { private set ; get ; } = string . Empty ;
55
53
56
- private IParseTreeVisitorResults ParseTreeValueResults { set ; get ; }
54
+ private IParseTreeVisitorResults ParseTreeValueResults { get ; }
57
55
58
56
public void InspectForUnreachableCases ( )
59
57
{
@@ -71,7 +69,9 @@ public void InspectForUnreachableCases()
71
69
foreach ( var range in caseClause . rangeClause ( ) )
72
70
{
73
71
var childResults = ParseTreeValueResults . GetChildResults ( range ) ;
74
- var childValues = childResults . Select ( ch => ParseTreeValueResults . GetValue ( ch ) ) ;
72
+ var childValues = childResults
73
+ . Select ( ch => ParseTreeValueResults . GetValue ( ch ) )
74
+ . ToList ( ) ;
75
75
if ( childValues . Any ( chr => chr . IsMismatchExpression ) )
76
76
{
77
77
containsMismatch = true ;
@@ -136,16 +136,16 @@ private IExpressionFilter BuildRangeClauseFilter(IEnumerable<VBAParser.CaseClaus
136
136
{
137
137
var rangeClauseFilter = ExpressionFilterFactory . Create ( SelectExpressionTypeName ) ;
138
138
139
- if ( ! ( GetVariableDeclarationTypeName is null ) )
139
+ if ( ! ( _getVariableDeclarationTypeName is null ) )
140
140
{
141
141
foreach ( var caseClause in caseClauses )
142
142
{
143
143
foreach ( var rangeClause in caseClause . rangeClause ( ) )
144
144
{
145
145
var expression = GetRangeClauseExpression ( rangeClause ) ;
146
- if ( ! expression . LHS . ParsesToConstantValue )
146
+ if ( ! expression ? . LHS ? . ParsesToConstantValue ?? false )
147
147
{
148
- var typeName = GetVariableDeclarationTypeName ( expression . LHS . Token , rangeClause ) ;
148
+ var typeName = _getVariableDeclarationTypeName ( expression . LHS . Token , rangeClause ) ;
149
149
rangeClauseFilter . AddComparablePredicateFilter ( expression . LHS . Token , typeName ) ;
150
150
}
151
151
}
@@ -157,12 +157,12 @@ private IExpressionFilter BuildRangeClauseFilter(IEnumerable<VBAParser.CaseClaus
157
157
private void SetSelectExpressionTypeName ( ParserRuleContext context , IParseTreeVisitorResults inspValues )
158
158
{
159
159
var selectStmt = ( VBAParser . SelectCaseStmtContext ) context ;
160
- if ( TryDetectTypeHint ( selectStmt . selectExpression ( ) . GetText ( ) , out string typeName )
160
+ if ( TryDetectTypeHint ( selectStmt . selectExpression ( ) . GetText ( ) , out var typeName )
161
161
&& InspectableTypes . Contains ( typeName ) )
162
162
{
163
163
SelectExpressionTypeName = typeName ;
164
164
}
165
- else if ( inspValues . TryGetValue ( selectStmt . selectExpression ( ) , out IParseTreeValue result )
165
+ else if ( inspValues . TryGetValue ( selectStmt . selectExpression ( ) , out var result )
166
166
&& InspectableTypes . Contains ( result . ValueType ) )
167
167
{
168
168
_selectExpressionValue = result ;
@@ -181,34 +181,38 @@ private string DeriveTypeFromCaseClauses(IParseTreeVisitorResults inspValues, VB
181
181
{
182
182
foreach ( var range in caseClause . rangeClause ( ) )
183
183
{
184
- if ( TryDetectTypeHint ( range . GetText ( ) , out string hintTypeName ) )
184
+ if ( TryDetectTypeHint ( range . GetText ( ) , out var hintTypeName ) )
185
185
{
186
186
caseClauseTypeNames . Add ( hintTypeName ) ;
187
187
}
188
188
else
189
189
{
190
- var typeNames = from context in range . children
191
- where context is ParserRuleContext
192
- && IsResultContext ( context )
193
- select inspValues . GetValueType ( context as ParserRuleContext ) ;
190
+ var typeNames = range . children
191
+ . OfType < ParserRuleContext > ( )
192
+ . Where ( IsResultContext )
193
+ . Select ( inspValues . GetValueType ) ;
194
194
195
195
caseClauseTypeNames . AddRange ( typeNames ) ;
196
196
caseClauseTypeNames . RemoveAll ( tp => ! InspectableTypes . Contains ( tp ) ) ;
197
197
}
198
198
}
199
199
}
200
200
201
- if ( TryGetSelectExpressionTypeNameFromTypes ( caseClauseTypeNames , out string evalTypeName ) )
201
+ if ( TryGetSelectExpressionTypeNameFromTypes ( caseClauseTypeNames , out var evalTypeName ) )
202
202
{
203
203
return evalTypeName ;
204
204
}
205
+
205
206
return string . Empty ;
206
207
}
207
208
208
- private static bool TryGetSelectExpressionTypeNameFromTypes ( IEnumerable < string > typeNames , out string typeName )
209
+ private static bool TryGetSelectExpressionTypeNameFromTypes ( ICollection < string > typeNames , out string typeName )
209
210
{
210
211
typeName = string . Empty ;
211
- if ( ! typeNames . Any ( ) ) { return false ; }
212
+ if ( ! typeNames . Any ( ) )
213
+ {
214
+ return false ;
215
+ }
212
216
213
217
//If everything is declared as a Variant , we do not attempt to inspect the selectStatement
214
218
if ( typeNames . All ( tn => tn . Equals ( Tokens . Variant ) ) )
@@ -229,7 +233,7 @@ private static bool TryGetSelectExpressionTypeNameFromTypes(IEnumerable<string>
229
233
return true ;
230
234
}
231
235
232
- //Mix of Integertypes and rational number types will be evaluated using Double or Currency
236
+ //Mix of Integer types and rational number types will be evaluated using Double or Currency
233
237
if ( typeNames . All ( tn => new List < string > ( ) { Tokens . Long , Tokens . Integer , Tokens . Byte , Tokens . Single , Tokens . Double , Tokens . Currency } . Contains ( tn ) ) )
234
238
{
235
239
typeName = typeNames . Any ( tk => tk . Equals ( Tokens . Currency ) ) ? Tokens . Currency : Tokens . Double ;
@@ -246,7 +250,7 @@ private static bool TryDetectTypeHint(string content, out string typeName)
246
250
return false ;
247
251
}
248
252
249
- if ( SymbolList . TypeHintToTypeName . Keys . Any ( th => content . EndsWith ( th ) ) )
253
+ if ( SymbolList . TypeHintToTypeName . Keys . Any ( content . EndsWith ) )
250
254
{
251
255
var lastChar = content . Substring ( content . Length - 1 ) ;
252
256
typeName = SymbolList . TypeHintToTypeName [ lastChar ] ;
@@ -257,9 +261,10 @@ private static bool TryDetectTypeHint(string content, out string typeName)
257
261
258
262
private IRangeClauseExpression GetRangeClauseExpression ( VBAParser . RangeClauseContext rangeClause )
259
263
{
260
- var resultContexts = from ctxt in rangeClause . children
261
- where ctxt is ParserRuleContext && IsResultContext ( ctxt )
262
- select ctxt as ParserRuleContext ;
264
+ var resultContexts = rangeClause . children
265
+ . OfType < ParserRuleContext > ( )
266
+ . Where ( IsResultContext )
267
+ . ToList ( ) ;
263
268
264
269
if ( ! resultContexts . Any ( ) )
265
270
{
@@ -272,41 +277,43 @@ private IRangeClauseExpression GetRangeClauseExpression(VBAParser.RangeClauseCon
272
277
var rangeEndValue = ParseTreeValueResults . GetValue ( rangeClause . GetChild < VBAParser . SelectEndValueContext > ( ) ) ;
273
278
return new RangeOfValuesExpression ( ( rangeStartValue , rangeEndValue ) ) ;
274
279
}
275
- else if ( rangeClause . IS ( ) != null )
280
+
281
+ if ( rangeClause . IS ( ) != null )
276
282
{
277
- var clauseValue = ParseTreeValueResults . GetValue ( resultContexts . First ( ) ) ;
283
+ var isClauseValue = ParseTreeValueResults . GetValue ( resultContexts . First ( ) ) ;
278
284
var opSymbol = rangeClause . GetChild < VBAParser . ComparisonOperatorContext > ( ) . GetText ( ) ;
279
- return new IsClauseExpression ( clauseValue , opSymbol ) ;
285
+ return new IsClauseExpression ( isClauseValue , opSymbol ) ;
280
286
}
281
- else if ( TryGetLogicSymbol ( resultContexts . First ( ) , out string symbol ) )
287
+
288
+ if ( ! TryGetLogicSymbol ( resultContexts . First ( ) , out string symbol ) )
282
289
{
283
- var resultContext = resultContexts . First ( ) ;
284
- var clauseValue = ParseTreeValueResults . GetValue ( resultContext ) ;
285
- if ( clauseValue . ParsesToConstantValue )
286
- {
287
- return new ValueExpression ( clauseValue ) ;
288
- }
290
+ return new ValueExpression ( ParseTreeValueResults . GetValue ( resultContexts . First ( ) ) ) ;
291
+ }
289
292
290
- if ( resultContext is VBAParser . LogicalNotOpContext )
291
- {
293
+ var resultContext = resultContexts . First ( ) ;
294
+ var clauseValue = ParseTreeValueResults . GetValue ( resultContext ) ;
295
+ if ( clauseValue . ParsesToConstantValue )
296
+ {
297
+ return new ValueExpression ( clauseValue ) ;
298
+ }
299
+
300
+ switch ( resultContext )
301
+ {
302
+ case VBAParser . LogicalNotOpContext _:
292
303
return new UnaryExpression ( clauseValue , symbol ) ;
293
- }
294
- else if ( resultContext is VBAParser . RelationalOpContext
295
- || resultContext is VBAParser . LogicalEqvOpContext
296
- || resultContext is VBAParser . LogicalImpOpContext )
304
+ case VBAParser . RelationalOpContext _:
305
+ case VBAParser . LogicalEqvOpContext _:
306
+ case VBAParser . LogicalImpOpContext _:
297
307
{
298
- ( IParseTreeValue lhs , IParseTreeValue rhs ) = CreateLogicPair ( clauseValue , symbol , _valueFactory ) ;
308
+ var ( lhs , rhs ) = CreateLogicPair ( clauseValue , symbol , _valueFactory ) ;
299
309
if ( symbol . Equals ( Tokens . Like ) )
300
310
{
301
311
return new LikeExpression ( lhs , rhs ) ;
302
312
}
303
313
return new BinaryExpression ( lhs , rhs , symbol ) ;
304
314
}
305
- return null ;
306
- }
307
- else
308
- {
309
- return new ValueExpression ( ParseTreeValueResults . GetValue ( resultContexts . First ( ) ) ) ;
315
+ default :
316
+ return null ;
310
317
}
311
318
}
312
319
@@ -323,8 +330,8 @@ private static bool TryGetLogicSymbol(ParserRuleContext context, out string opSy
323
330
private static ( IParseTreeValue lhs , IParseTreeValue rhs )
324
331
CreateLogicPair ( IParseTreeValue value , string opSymbol , IParseTreeValueFactory factory )
325
332
{
326
- var operands = value . Token . Split ( new string [ ] { opSymbol } , StringSplitOptions . None ) ;
327
- if ( operands . Count ( ) == 2 )
333
+ var operands = value . Token . Split ( new [ ] { opSymbol } , StringSplitOptions . None ) ;
334
+ if ( operands . Length == 2 )
328
335
{
329
336
var lhs = factory . Create ( operands [ 0 ] . Trim ( ) ) ;
330
337
var rhs = factory . Create ( operands [ 1 ] . Trim ( ) ) ;
@@ -335,7 +342,7 @@ private static (IParseTreeValue lhs, IParseTreeValue rhs)
335
342
return ( lhs , rhs ) ;
336
343
}
337
344
338
- if ( operands . Count ( ) == 1 )
345
+ if ( operands . Length == 1 )
339
346
{
340
347
var lhs = factory . Create ( operands [ 0 ] . Trim ( ) ) ;
341
348
return ( lhs , null ) ;
@@ -358,7 +365,7 @@ private static bool IsResultContext<TContext>(TContext context)
358
365
|| context is VBAParser . SelectEndValueContext ;
359
366
}
360
367
361
- private static List < string > InspectableTypes = new List < string > ( )
368
+ private static readonly IReadOnlyList < string > InspectableTypes = new List < string >
362
369
{
363
370
Tokens . Byte ,
364
371
Tokens . Integer ,
0 commit comments