@@ -2441,44 +2441,6 @@ End Sub
2441
2441
Assert . AreEqual ( expectedMsg , actualMsg ) ;
2442
2442
}
2443
2443
2444
- [ TestCase ( "vbBack" , "\b " ) ]
2445
- [ TestCase ( "vbCrLf" , "\r \n " ) ]
2446
- [ TestCase ( "vbCr" , "\r " ) ]
2447
- [ TestCase ( "vbLf" , "\n " ) ]
2448
- [ TestCase ( "vbFormFeed" , "\f " ) ]
2449
- [ TestCase ( "vbNewLine" , "\r \n " ) ]
2450
- [ TestCase ( "vbNullChar" , "\0 " ) ]
2451
- [ TestCase ( "vbNullString" , null ) ]
2452
- [ TestCase ( "vbTab" , "\t " ) ]
2453
- [ TestCase ( "vbVerticalTab" , "\v " ) ]
2454
- [ Category ( "Inspections" ) ]
2455
- public void UnreachableCaseInspection_VbStringConstantToLiteral_AreEqual ( string constToken , string expected )
2456
- {
2457
- var parseTreeValueVisitor = new ParseTreeValueVisitor ( null , new List < VBAParser . EnumerationStmtContext > ( ) , null ) as ITestParseTreeVisitor ;
2458
- if ( parseTreeValueVisitor . IsVBStringConstant ( constToken , out string literalValue ) )
2459
- {
2460
- Assert . AreEqual ( expected , literalValue ) ;
2461
- return ;
2462
- }
2463
- Assert . Fail ( $ "TryConvertVBStringConstantToLiteral failed to convert { constToken } ") ;
2464
- }
2465
-
2466
- [ TestCase ( "\r " , true ) ]
2467
- [ TestCase ( "\r \n " , true ) ]
2468
- [ TestCase ( "\b " , true ) ]
2469
- [ TestCase ( "\f " , true ) ]
2470
- [ TestCase ( "\0 " , true ) ]
2471
- [ TestCase ( "\t " , true ) ]
2472
- [ TestCase ( "\v " , true ) ]
2473
- [ TestCase ( null , false ) ]
2474
- [ Category ( "Inspections" ) ]
2475
- public void UnreachableCaseInspection_ControlCharToLiteral_AreEqual ( string constToken , bool expected )
2476
- {
2477
- var parseTreeValueVisitor = new ParseTreeValueVisitor ( null , new List < VBAParser . EnumerationStmtContext > ( ) , null ) as ITestParseTreeVisitor ;
2478
- Assert . AreEqual ( expected , parseTreeValueVisitor . IsNonPrintingControlCharacter ( constToken ) ) ;
2479
- }
2480
-
2481
- //https://github.com/rubberduck-vba/Rubberduck/issues/4659
2482
2444
[ Test ]
2483
2445
[ Category ( "Inspections" ) ]
2484
2446
public void UnreachableCaseInspection_VbObjectErrorConstant ( )
@@ -2504,14 +2466,6 @@ Case vbObjectError + 1 'unreachable
2504
2466
End Select
2505
2467
End Sub
2506
2468
" ;
2507
- ( bool IsType , string ExpressionValue , string TypeName ) TestGetValuedDeclaration ( Declaration declaration )
2508
- {
2509
- if ( declaration . IdentifierName . Equals ( "vbObjectError" ) )
2510
- {
2511
- return ( true , "-2147221504" , Tokens . Long ) ;
2512
- }
2513
- return ( false , null , null ) ;
2514
- }
2515
2469
2516
2470
var vbe = CreateStandardModuleProject ( inputCode ) ;
2517
2471
@@ -2533,26 +2487,81 @@ End Sub
2533
2487
}
2534
2488
2535
2489
//https://github.com/rubberduck-vba/Rubberduck/issues/4680
2536
- [ Test ]
2537
- [ Ignore ( "Issue 4680" ) ]
2538
- [ Category ( "Inspections" ) ]
2539
- public void UnreachableCaseInspection_VbStringConstant ( )
2540
- {
2490
+ [ TestCase ( "vbNewLine" , "vbCr + vbLf" ) ]
2491
+ [ TestCase ( "vbNewLine" , "Chr(13) + Chr(10)" ) ]
2492
+ [ TestCase ( "vbNewLine" , "Chr$(13) + Chr$(10)" ) ]
2493
+ [ TestCase ( "Chr(13) + Chr(10)" , "Chr$(13) + Chr$(10)" ) ]
2494
+ [ TestCase ( "vbCr + vbLf" , "vbNewLine" ) ]
2495
+ [ TestCase ( "vbCr + Chr(10)" , "vbNewLine" ) ]
2496
+ [ TestCase ( "Chr(13) + vbLf" , "vbNewLine" ) ]
2497
+ [ TestCase ( "Chr(0)" , "vbNullChar" ) ]
2498
+ [ TestCase ( "Chr$(0)" , "vbNullChar" ) ]
2499
+ [ TestCase ( "Chr(8)" , "vbBack" ) ]
2500
+ [ TestCase ( "Chr$(8)" , "vbBack" ) ]
2501
+ [ TestCase ( "Chr(12)" , "vbFormFeed" ) ]
2502
+ [ TestCase ( "Chr$(12)" , "vbFormFeed" ) ]
2503
+ [ TestCase ( "Chr(9)" , "vbTab" ) ]
2504
+ [ TestCase ( "Chr$(9)" , "vbTab" ) ]
2505
+ [ TestCase ( "Chr(11)" , "vbVerticalTab" ) ]
2506
+ [ TestCase ( "Chr$(11)" , "vbVerticalTab" ) ]
2507
+ [ Category ( "Inspections" ) ]
2508
+ public void UnreachableCaseInspection_NonPrintingControlConstants ( string testCase , string equivalent )
2509
+ {
2510
+ var expectedUnreachableCount = 1 ;
2541
2511
string inputCode =
2542
- @"
2512
+ $ @ "
2543
2513
Sub Foo(value As String)
2544
2514
Select Case value
2545
- Case ""Hello"" + vbNewLine + ""World""
2546
- MsgBox ""vbNewLine version""
2547
- Case ""Hello"" + vbCr + vbLf + ""World"" 'unreachable
2548
- MsgBox ""vbCr + vbLf version""
2515
+ Case ""Hello"" + { testCase } + ""World""
2516
+ MsgBox ""testCase version""
2517
+ Case ""Hello"" + { equivalent } + ""World"" 'unreachable
2518
+ MsgBox ""equivalent version""
2549
2519
Case ""Reachable""
2550
2520
MsgBox ""Reachable""
2551
2521
End Select
2552
2522
End Sub
2553
2523
" ;
2554
- ( string expectedMsg , string actualMsg ) = CheckActualResultsEqualsExpected ( inputCode , unreachable : 1 ) ;
2555
- Assert . AreEqual ( expectedMsg , actualMsg ) ;
2524
+ var vbe = CreateStandardModuleProject ( inputCode ) ;
2525
+
2526
+ IEnumerable < Rubberduck . Parsing . Inspections . Abstract . IInspectionResult > actualResults ;
2527
+ using ( var state = MockParser . CreateAndParse ( vbe . Object ) )
2528
+ {
2529
+ var inspection = new UnreachableCaseInspection ( state ) ;
2530
+ var parseTreeValueVisitor = inspection . ParseTreeValueVisitor as ITestParseTreeVisitor ;
2531
+
2532
+ parseTreeValueVisitor . InjectValuedDeclarationEvaluator ( TestGetValuedDeclaration ) ;
2533
+
2534
+ var inspector = InspectionsHelper . GetInspector ( inspection ) ;
2535
+ actualResults = inspector . FindIssuesAsync ( state , CancellationToken . None ) . Result ;
2536
+ }
2537
+
2538
+ var actualUnreachable = actualResults . Where ( ar => ar . Description . Equals ( InspectionResults . UnreachableCaseInspection_Unreachable ) ) ;
2539
+
2540
+ Assert . AreEqual ( expectedUnreachableCount , actualUnreachable . Count ( ) ) ;
2541
+ }
2542
+
2543
+ private static Dictionary < string , ( string , string ) > _vbConstConversions = new Dictionary < string , ( string , string ) > ( )
2544
+ {
2545
+ [ "vbNewLine" ] = ( "Chr$(13) & Chr$(10)" , Tokens . String ) ,
2546
+ [ "vbCr" ] = ( "Chr$(13)" , Tokens . String ) ,
2547
+ [ "vbLf" ] = ( "Chr$(10)" , Tokens . String ) ,
2548
+ [ "vbNullChar" ] = ( "Chr$(0)" , Tokens . String ) ,
2549
+ [ "vbBack" ] = ( "Chr$(8)" , Tokens . String ) ,
2550
+ [ "vbTab" ] = ( "Chr$(9)" , Tokens . String ) ,
2551
+ [ "vbVerticalTab" ] = ( "Chr$(11)" , Tokens . String ) ,
2552
+ [ "vbFormFeed" ] = ( "Chr$(12)" , Tokens . String ) ,
2553
+ [ "vbObjectError" ] = ( "-2147221504" , Tokens . Long ) ,
2554
+ } ;
2555
+
2556
+ private static ( bool IsType , string ExpressionValue , string TypeName ) TestGetValuedDeclaration ( Declaration declaration )
2557
+ {
2558
+ if ( ! _vbConstConversions . ContainsKey ( declaration . IdentifierName ) )
2559
+ {
2560
+ return ( false , null , null ) ;
2561
+ }
2562
+
2563
+ ( string expressionValue , string typename ) = _vbConstConversions [ declaration . IdentifierName ] ;
2564
+ return ( true , expressionValue , typename ) ;
2556
2565
}
2557
2566
2558
2567
private static ( string expectedMsg , string actualMsg ) CheckActualResultsEqualsExpected ( string inputCode , int unreachable = 0 , int mismatch = 0 , int caseElse = 0 , int inherentlyUnreachable = 0 , int overflow = 0 )
0 commit comments