Skip to content

Commit 8cbe8f8

Browse files
committed
Add handling for NonPrinting string constants
1 parent 0ac10df commit 8cbe8f8

File tree

4 files changed

+114
-87
lines changed

4 files changed

+114
-87
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection/ParseTreeValue.cs

Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using Rubberduck.Parsing.Grammar;
22
using Rubberduck.Parsing.PreProcessing;
33
using System;
4+
using System.Collections.Generic;
45
using System.Globalization;
56

67
namespace Rubberduck.Inspections.Concrete.UnreachableCaseInspection
@@ -22,6 +23,31 @@ public struct ParseTreeValue : IParseTreeValue
2223
private StringLiteralExpression _stringConstant;
2324
private bool? _exceedsValueTypeRange;
2425

26+
private static Dictionary<string,string> ControlCharacterCompareTokens = new Dictionary<string, string>()
27+
{
28+
["Chr$(8)"] = "Chr$(8)", //vbBack
29+
["Chr$(13)"] = "Chr$(13)", //vbCr
30+
["Chr$(13) + Chr$(10)"] = "Chr$(13)Chr$(10)", //vbCrLf
31+
["Chr$(10)"] = "Chr$(10)", //vbLf
32+
["Chr$(12)"] = "Chr$(12)", //vbFormFeed
33+
["Chr$(13) & Chr$(10)"] = "Chr$(13)Chr$(10)", //vbNewLine
34+
["Chr$(0)"] = "Chr$(0)", //vbNullChar
35+
["Chr$(9)"] = "Chr$(9)", //vbTab
36+
["Chr$(11)"] = "Chr$(11)", //vbVerticalTab
37+
["Chr$(13)Chr$(10)"] = "Chr$(13)Chr$(10)",
38+
};
39+
40+
public static bool TryGetNonPrintingControlCharCompareToken(string controlCharCandidate, out string comparableToken)
41+
{
42+
comparableToken = controlCharCandidate;
43+
if (controlCharCandidate.StartsWith(Tokens.Chr))
44+
{
45+
var key = controlCharCandidate.Replace("Chr(", "Chr$(");
46+
return ControlCharacterCompareTokens.TryGetValue(key, out comparableToken);
47+
}
48+
return false;
49+
}
50+
2551
public static IParseTreeValue CreateValueType(TypeTokenPair value)
2652
{
2753
if (value.ValueType.Equals(Tokens.Date) || value.ValueType.Equals(Tokens.String))
@@ -89,6 +115,11 @@ public ParseTreeValue(TypeTokenPair valuePair)
89115
_stringConstant = new StringLiteralExpression(new ConstantExpression(new StringValue(_typeTokenPair.Token)));
90116
ParsesToConstantValue = true;
91117
}
118+
else if (valuePair.ValueType.Equals(Tokens.String)
119+
&& TryGetNonPrintingControlCharCompareToken(valuePair.Token, out _))
120+
{
121+
ParsesToConstantValue = true;
122+
}
92123
}
93124

94125
public string ValueType => _typeTokenPair.ValueType;

Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection/ParseTreeValueFactory.cs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -72,6 +72,12 @@ public IParseTreeValue CreateDeclaredType(string expression, string declaredType
7272
throw new ArgumentNullException();
7373
}
7474

75+
if (ParseTreeValue.TryGetNonPrintingControlCharCompareToken(expression, out string comparableToken))
76+
{
77+
var charConversion = new TypeTokenPair(Tokens.String, comparableToken);
78+
return ParseTreeValue.CreateValueType(charConversion);
79+
}
80+
7581
var goalTypeTokenPair = new TypeTokenPair(declaredTypeName, null);
7682
var typeToken = TypeTokenPair.ConformToType(declaredTypeName, expression);
7783
if (typeToken.HasValue)

Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection/ParseTreeValueVisitor.cs

Lines changed: 10 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -16,8 +16,6 @@ public interface IParseTreeValueVisitor : IParseTreeVisitor<IParseTreeVisitorRes
1616

1717
public interface ITestParseTreeVisitor
1818
{
19-
bool IsVBStringConstant(string token, out string literalValue);
20-
bool IsNonPrintingControlCharacter(string token);
2119
void InjectValuedDeclarationEvaluator(Func<Declaration, (bool, string, string)> func);
2220
}
2321

@@ -41,20 +39,6 @@ public EnumMember(VBAParser.EnumerationStmt_ConstantContext constContext, long i
4139
private List<VBAParser.EnumerationStmtContext> _enumStmtContexts;
4240
private List<EnumMember> _enumMembers;
4341

44-
private static Dictionary<string, string> _vbStringConstants = new Dictionary<string, string>()
45-
{
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(),
56-
};
57-
5842
public ParseTreeValueVisitor(IParseTreeValueFactory valueFactory, List<VBAParser.EnumerationStmtContext> allEnums, Func<ParserRuleContext, (bool success, IdentifierReference idRef)> idRefRetriever)
5943
{
6044
_inspValueFactory = valueFactory;
@@ -291,6 +275,14 @@ private bool TryGetLExprValue(VBAParser.LExprContext lExprContext, out string ex
291275
return true;
292276
}
293277

278+
if (lExprContext.TryGetChildContext(out VBAParser.IndexExprContext idxExpr)
279+
&& ParseTreeValue.TryGetNonPrintingControlCharCompareToken(idxExpr.GetText(), out string comparableToken))
280+
{
281+
declaredTypeName = Tokens.String;
282+
expressionValue = comparableToken;
283+
return true;
284+
}
285+
294286
return false;
295287
}
296288

@@ -336,14 +328,9 @@ private void GetContextValue(ParserRuleContext context, out string declaredTypeN
336328
expressionValue = ExpressionValue;
337329
declaredTypeName = TypeName;
338330

339-
if (IsVBStringConstant(expressionValue, out string constLiteral))
340-
{
341-
declaredTypeName = Tokens.String;
342-
expressionValue = constLiteral;
343-
return;
344-
}
345-
else if (IsNonPrintingControlCharacter(expressionValue))
331+
if (ParseTreeValue.TryGetNonPrintingControlCharCompareToken(expressionValue, out string resolvedValue))
346332
{
333+
expressionValue = resolvedValue;
347334
declaredTypeName = Tokens.String;
348335
return;
349336
}
@@ -450,12 +437,6 @@ private static bool IsBinaryOpEvaluationContext<T>(T context)
450437
return false;
451438
}
452439

453-
public bool IsVBStringConstant(string candidate, out string literal)
454-
=> _vbStringConstants.TryGetValue(candidate, out literal);
455-
456-
public bool IsNonPrintingControlCharacter(string controlChar)
457-
=> controlChar != null && _vbStringConstants.ContainsValue(controlChar);
458-
459440
public void InjectValuedDeclarationEvaluator( Func<Declaration, (bool, string, string)> func)
460441
=> ValuedDeclarationEvaluator = func;
461442

RubberduckTests/Inspections/UnreachableCase/UnreachableCaseInspectionTests.cs

Lines changed: 67 additions & 58 deletions
Original file line numberDiff line numberDiff line change
@@ -2441,44 +2441,6 @@ End Sub
24412441
Assert.AreEqual(expectedMsg, actualMsg);
24422442
}
24432443

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
24822444
[Test]
24832445
[Category("Inspections")]
24842446
public void UnreachableCaseInspection_VbObjectErrorConstant()
@@ -2504,14 +2466,6 @@ Case vbObjectError + 1 'unreachable
25042466
End Select
25052467
End Sub
25062468
";
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-
}
25152469

25162470
var vbe = CreateStandardModuleProject(inputCode);
25172471

@@ -2533,26 +2487,81 @@ End Sub
25332487
}
25342488

25352489
//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;
25412511
string inputCode =
2542-
@"
2512+
$@"
25432513
Sub Foo(value As String)
25442514
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""
25492519
Case ""Reachable""
25502520
MsgBox ""Reachable""
25512521
End Select
25522522
End Sub
25532523
";
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);
25562565
}
25572566

25582567
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

Comments
 (0)