@@ -14,7 +14,14 @@ public interface IParseTreeValueVisitor : IParseTreeVisitor<IParseTreeVisitorRes
14
14
event EventHandler < ValueResultEventArgs > OnValueResultCreated ;
15
15
}
16
16
17
- public class ParseTreeValueVisitor : IParseTreeValueVisitor
17
+ public interface ITestParseTreeVisitor
18
+ {
19
+ bool IsVBStringConstantToLiteral ( string token , out string literalValue ) ;
20
+ bool IsNonPrintingControlCharacter ( string token ) ;
21
+ void InjectValuedDeclarationEvaluator ( Func < Declaration , ( bool , string , string ) > func ) ;
22
+ }
23
+
24
+ public class ParseTreeValueVisitor : IParseTreeValueVisitor , ITestParseTreeVisitor
18
25
{
19
26
private class EnumMember
20
27
{
@@ -34,18 +41,18 @@ public EnumMember(VBAParser.EnumerationStmt_ConstantContext constContext, long i
34
41
private List < VBAParser . EnumerationStmtContext > _enumStmtContexts ;
35
42
private List < EnumMember > _enumMembers ;
36
43
37
- private static List < KeyValuePair < string , string > > _vbStringConstants = new List < KeyValuePair < string , string > > ( )
44
+ private static Dictionary < string , string > _vbStringConstants = new Dictionary < string , string > ( )
38
45
{
39
- new KeyValuePair < string , string > ( Tokens . vbBack , ( ( char ) 8 ) . ToString ( ) ) ,
40
- new KeyValuePair < string , string > ( Tokens . vbCr , ( ( char ) 13 ) . ToString ( ) ) ,
41
- new KeyValuePair < string , string > ( Tokens . vbCrLf , ( ( char ) 13 ) . ToString ( ) + ( ( char ) 10 ) . ToString ( ) ) ,
42
- new KeyValuePair < string , string > ( Tokens . vbLf , ( ( char ) 10 ) . ToString ( ) ) ,
43
- new KeyValuePair < string , string > ( Tokens . vbFormFeed , ( ( char ) 12 ) . ToString ( ) ) ,
44
- new KeyValuePair < string , string > ( Tokens . vbNewLine , Environment . NewLine ) ,
45
- new KeyValuePair < string , string > ( Tokens . vbNullChar , ( ( char ) 0 ) . ToString ( ) ) ,
46
- new KeyValuePair < string , string > ( Tokens . vbNullString , null ) ,
47
- new KeyValuePair < string , string > ( Tokens . vbTab , ( ( char ) 9 ) . ToString ( ) ) ,
48
- new KeyValuePair < string , string > ( Tokens . vbVerticalTab , ( ( char ) 11 ) . ToString ( ) ) ,
46
+ [ Tokens . vbBack ] = ( ( char ) 8 ) . ToString ( ) ,
47
+ [ Tokens . vbCr ] = ( ( char ) 13 ) . ToString ( ) ,
48
+ [ Tokens . vbCrLf ] = ( ( char ) 13 ) . ToString ( ) + ( ( char ) 10 ) . ToString ( ) ,
49
+ [ Tokens . vbLf ] = ( ( char ) 10 ) . ToString ( ) ,
50
+ [ Tokens . vbFormFeed ] = ( ( char ) 12 ) . ToString ( ) ,
51
+ [ Tokens . vbNewLine ] = Environment . NewLine ,
52
+ [ Tokens . vbNullChar ] = ( ( char ) 0 ) . ToString ( ) ,
53
+ [ Tokens . vbNullString ] = null ,
54
+ [ Tokens . vbTab ] = ( ( char ) 9 ) . ToString ( ) ,
55
+ [ Tokens . vbVerticalTab ] = ( ( char ) 11 ) . ToString ( ) ,
49
56
} ;
50
57
51
58
public ParseTreeValueVisitor ( IParseTreeValueFactory valueFactory , List < VBAParser . EnumerationStmtContext > allEnums , Func < ParserRuleContext , ( bool success , IdentifierReference idRef ) > idRefRetriever )
@@ -55,8 +62,6 @@ public ParseTreeValueVisitor(IParseTreeValueFactory valueFactory, List<VBAParser
55
62
_contextValues = new ParseTreeVisitorResults ( ) ;
56
63
OnValueResultCreated += _contextValues . OnNewValueResult ;
57
64
_enumStmtContexts = allEnums ;
58
- _enumMembers = new List < EnumMember > ( ) ;
59
- LoadEnumMemberValues ( ) ;
60
65
}
61
66
62
67
private Func < ParserRuleContext , ( bool success , IdentifierReference idRef ) > IdRefRetriever { set ; get ; } = null ;
@@ -289,6 +294,30 @@ private bool TryGetLExprValue(VBAParser.LExprContext lExprContext, out string ex
289
294
return false ;
290
295
}
291
296
297
+ private Func < Declaration , ( bool , string , string ) > _valueDeclarationEvaluator ;
298
+ private Func < Declaration , ( bool , string , string ) > ValuedDeclarationEvaluator
299
+ {
300
+ set
301
+ {
302
+ _valueDeclarationEvaluator = value ;
303
+ }
304
+ get
305
+ {
306
+ return _valueDeclarationEvaluator ?? GetValuedDeclaration ;
307
+ }
308
+ }
309
+
310
+
311
+ private ( bool IsType , string ExpressionValue , string TypeName ) GetValuedDeclaration ( Declaration declaration )
312
+ {
313
+ if ( declaration is ValuedDeclaration valuedDeclaration )
314
+ {
315
+ var typeName = GetBaseTypeForDeclaration ( declaration ) ;
316
+ return ( true , valuedDeclaration . Expression , typeName ) ;
317
+ }
318
+ return ( false , null , null ) ;
319
+ }
320
+
292
321
private void GetContextValue ( ParserRuleContext context , out string declaredTypeName , out string expressionValue )
293
322
{
294
323
expressionValue = context . GetText ( ) ;
@@ -300,20 +329,25 @@ private void GetContextValue(ParserRuleContext context, out string declaredTypeN
300
329
expressionValue = rangeClauseIdentifierReference . IdentifierName ;
301
330
declaredTypeName = GetBaseTypeForDeclaration ( declaration ) ;
302
331
303
- if ( declaration is ValuedDeclaration valuedDeclaration )
332
+ ( bool IsValuedDeclaration , string ExpressionValue , string TypeName ) = ValuedDeclarationEvaluator ( declaration ) ;
333
+
334
+ if ( IsValuedDeclaration )
304
335
{
305
- expressionValue = valuedDeclaration . Expression ;
306
- declaredTypeName = GetBaseTypeForDeclaration ( declaration ) ;
307
- if ( IsVBStringConstant ( expressionValue ) )
336
+ expressionValue = ExpressionValue ;
337
+ declaredTypeName = TypeName ;
338
+
339
+ if ( IsVBStringConstantToLiteral ( expressionValue , out string constLiteral ) )
308
340
{
309
- //Returning here ensures the typename is correct,
310
- //but only identical (copy/paste) equivalence involving
311
- //constants like vbNewLine will be flagged
312
341
declaredTypeName = Tokens . String ;
342
+ expressionValue = constLiteral ;
313
343
return ;
314
344
}
315
-
316
- if ( long . TryParse ( expressionValue , out _ ) )
345
+ else if ( IsNonPrintingControlCharacter ( expressionValue ) )
346
+ {
347
+ declaredTypeName = Tokens . String ;
348
+ return ;
349
+ }
350
+ else if ( long . TryParse ( expressionValue , out _ ) )
317
351
{
318
352
return ;
319
353
}
@@ -329,6 +363,10 @@ private void GetContextValue(ParserRuleContext context, out string declaredTypeN
329
363
expressionValue = GetConstantContextValueToken ( declaration . Context ) ;
330
364
if ( expressionValue . Equals ( string . Empty ) )
331
365
{
366
+ if ( _enumMembers is null )
367
+ {
368
+ LoadEnumMemberValues ( ) ;
369
+ }
332
370
var enumValue = _enumMembers . SingleOrDefault ( dt => dt . ConstantContext == declaration . Context ) ;
333
371
expressionValue = enumValue ? . Value . ToString ( ) ?? string . Empty ;
334
372
}
@@ -412,11 +450,24 @@ private static bool IsBinaryOpEvaluationContext<T>(T context)
412
450
return false ;
413
451
}
414
452
415
- private static bool IsVBStringConstant ( string candidate )
416
- => _vbStringConstants . Exists ( kv => kv . Key . Equals ( candidate ) ) ;
453
+ public bool IsVBStringConstantToLiteral ( string candidate , out string literal )
454
+ {
455
+ return _vbStringConstants . TryGetValue ( candidate , out literal ) ;
456
+ }
457
+
458
+ public bool IsNonPrintingControlCharacter ( string controlChar )
459
+ {
460
+ return controlChar != null && _vbStringConstants . ContainsValue ( controlChar ) ;
461
+ }
462
+
463
+ public void InjectValuedDeclarationEvaluator ( Func < Declaration , ( bool , string , string ) > func )
464
+ {
465
+ ValuedDeclarationEvaluator = func ;
466
+ }
417
467
418
468
private void LoadEnumMemberValues ( )
419
469
{
470
+ _enumMembers = new List < EnumMember > ( ) ;
420
471
foreach ( var enumStmt in _enumStmtContexts )
421
472
{
422
473
long enumAssignedValue = - 1 ;
0 commit comments