Skip to content

Commit 8786184

Browse files
committed
Merge branch 'rubberduck-vba/next' into InterfaceMemberCodeResuse
2 parents dc2b7dc + a425932 commit 8786184

File tree

7 files changed

+80
-8
lines changed

7 files changed

+80
-8
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/SheetAccessedUsingStringInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -100,7 +100,7 @@ protected override (bool isResult, string properties) IsResultReferenceWithAddit
100100
}
101101

102102
var projectId = reference.QualifiedModuleName.ProjectId;
103-
var sheetName = sheetNameArgumentLiteralExpressionContext.GetText().UnQuote();
103+
var sheetName = sheetNameArgumentLiteralExpressionContext.GetText().FromVbaStringLiteral();
104104
var codeName = CodeNameOfVBComponentMatchingSheetName(projectId, sheetName);
105105

106106
if (codeName == null)

Rubberduck.JunkDrawer/Output/StringExtensions.cs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -66,6 +66,16 @@ public static string EnQuote(this string input)
6666
return $"\"{input}\"";
6767
}
6868

69+
public static string FromVbaStringLiteral(this string input)
70+
{
71+
return input.UnQuote().Replace("\"\"", "\"");
72+
}
73+
74+
public static string ToVbaStringLiteral(this string input)
75+
{
76+
return input.Replace("\"", "\"\"");
77+
}
78+
6979
public static bool TryMatchHungarianNotationCriteria(this string identifier, out string nonHungarianName)
7080
{
7181
nonHungarianName = identifier;

Rubberduck.Parsing/Annotations/Concrete/ObsoleteAnnotation.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ public override IReadOnlyList<string> ProcessAnnotationArguments(IEnumerable<str
2020
var args = arguments.ToList();
2121

2222
ReplacementDocumentation = args.Any()
23-
? args[0].UnQuote()
23+
? args[0]
2424
: string.Empty;
2525

2626
return base.ProcessAnnotationArguments(args);

Rubberduck.Parsing/Annotations/Concrete/TestMethodAnnotation.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ public TestMethodAnnotation()
1515

1616
public IReadOnlyList<string> ProcessAnnotationArguments(IEnumerable<string> arguments)
1717
{
18-
var firstParameter = arguments.FirstOrDefault()?.UnQuote();
18+
var firstParameter = arguments.FirstOrDefault();
1919
var result = new List<string>();
2020
if (!string.IsNullOrWhiteSpace(firstParameter))
2121
{

Rubberduck.UnitTesting/UnitTesting/TestMethod.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -25,8 +25,8 @@ public TestCategory Category
2525
{
2626
get
2727
{
28-
var testMethodAnnotation = Declaration.Annotations.Where(pta => pta.Annotation is TestMethodAnnotation).First();
29-
var argument = testMethodAnnotation.AnnotationArguments.FirstOrDefault()?.UnQuote();
28+
var testMethodAnnotation = Declaration.Annotations.First(pta => pta.Annotation is TestMethodAnnotation);
29+
var argument = testMethodAnnotation.AnnotationArguments.FirstOrDefault()?.FromVbaStringLiteral();
3030

3131
var categorization = string.IsNullOrWhiteSpace(argument)
3232
? TestExplorer.TestExplorer_Uncategorized

RubberduckTests/Inspections/SheetAccessedUsingStringInspectionTests.cs

Lines changed: 41 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,45 @@ public void SheetAccessedUsingString_ReturnsResult_AccessingUsingWorkbookModule(
2727
Assert.AreEqual(2, ArrangeParserAndGetResults(inputCode).Count());
2828
}
2929

30+
[Test]
31+
[Category("Inspections")]
32+
public void SheetAccessedUsingString_DoesNotReturnResult_NoDocumentWithSheetName()
33+
{
34+
const string inputCode =
35+
@"Public Sub Foo()
36+
ThisWorkbook.Worksheets(""Sheet1"").Range(""A1"") = ""Foo""
37+
ThisWorkbook.Sheets(""Sheet1"").Range(""A1"") = ""Foo""
38+
End Sub";
39+
40+
Assert.AreEqual(0, ArrangeParserAndGetResults(inputCode, "NotSheet1").Count());
41+
}
42+
43+
[Test]
44+
[Category("Inspections")]
45+
public void SheetAccessedUsingString_ReturnsResult_CodeNameAndSheetNameDifferent()
46+
{
47+
const string inputCode =
48+
@"Public Sub Foo()
49+
ThisWorkbook.Worksheets(""NotSheet1"").Range(""A1"") = ""Foo""
50+
ThisWorkbook.Sheets(""NotSheet1"").Range(""A1"") = ""Foo""
51+
End Sub";
52+
53+
Assert.AreEqual(2, ArrangeParserAndGetResults(inputCode, "NotSheet1").Count());
54+
}
55+
56+
[Test]
57+
[Category("Inspections")]
58+
public void SheetAccessedUsingString_ReturnsResult_SheetNameContainsDoubleQuotes()
59+
{
60+
const string inputCode =
61+
@"Public Sub Foo()
62+
ThisWorkbook.Worksheets(""She""""et1"").Range(""A1"") = ""Foo""
63+
ThisWorkbook.Sheets(""She""""et1"").Range(""A1"") = ""Foo""
64+
End Sub";
65+
66+
Assert.AreEqual(2, ArrangeParserAndGetResults(inputCode, "She\"et1").Count());
67+
}
68+
3069
[Test]
3170
[Category("Inspections")]
3271
//Access via Application is an access on the ActiveWorkbook, not necessarily ThisWorkbook.
@@ -172,7 +211,7 @@ Dim s As String
172211
Assert.AreEqual(0, ArrangeParserAndGetResults(inputCode).Count());
173212
}
174213

175-
private IEnumerable<IInspectionResult> ArrangeParserAndGetResults(string inputCode)
214+
private IEnumerable<IInspectionResult> ArrangeParserAndGetResults(string inputCode, string sheetName = "Sheet1")
176215
{
177216
var builder = new MockVbeBuilder();
178217

@@ -190,7 +229,7 @@ private IEnumerable<IInspectionResult> ArrangeParserAndGetResults(string inputCo
190229
.AddComponent("Sheet1", ComponentType.Document, "",
191230
properties: new[]
192231
{
193-
CreateVBComponentPropertyMock("Name", "Sheet1").Object,
232+
CreateVBComponentPropertyMock("Name", sheetName).Object,
194233
CreateVBComponentPropertyMock("CodeName", "Sheet1").Object
195234
})
196235
.AddReference("ReferencedProject", string.Empty, 0, 0)

RubberduckTests/QuickFixes/AccessSheetUsingCodeNameQuickFixTests.cs

Lines changed: 24 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,24 @@ Public Sub Foo()
3131
Assert.AreEqual(expectedCode, actualCode);
3232
}
3333

34+
[Test]
35+
[Category("QuickFixes")]
36+
public void SheetAccessedUsingString_QuickFixWorks_SheetNameContainingDoubleQuotes()
37+
{
38+
const string inputCode = @"
39+
Public Sub Foo()
40+
ThisWorkbook.Sheets(""She""""et1"").Range(""A1"") = ""foo""
41+
End Sub";
42+
43+
const string expectedCode = @"
44+
Public Sub Foo()
45+
Sheet1.Range(""A1"") = ""foo""
46+
End Sub";
47+
var vbe = TestVbe(inputCode, "She\"et1", out _);
48+
var actualCode = ApplyQuickFixToFirstInspectionResult(vbe, "Module1", state => new SheetAccessedUsingStringInspection(state, state.ProjectsProvider));
49+
Assert.AreEqual(expectedCode, actualCode);
50+
}
51+
3452
[Test]
3553
[Category("QuickFixes")]
3654
public void SheetAccessedUsingString_QuickFixWorks_AssigningSheetToVariable()
@@ -191,14 +209,19 @@ protected override IQuickFix QuickFix(RubberduckParserState state)
191209
}
192210

193211
protected override IVBE TestVbe(string code, out IVBComponent component)
212+
{
213+
return TestVbe(code, "Sheet1", out component);
214+
}
215+
216+
private IVBE TestVbe(string code, string sheetName, out IVBComponent component)
194217
{
195218
var builder = new MockVbeBuilder();
196219
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
197220
.AddComponent("Module1", ComponentType.StandardModule, code)
198221
.AddComponent("Sheet1", ComponentType.Document, "",
199222
properties: new[]
200223
{
201-
CreateVBComponentPropertyMock("Name", "Sheet1").Object,
224+
CreateVBComponentPropertyMock("Name", sheetName).Object,
202225
CreateVBComponentPropertyMock("CodeName", "Sheet1").Object
203226
})
204227
.AddComponent("SheetWithDifferentCodeName", ComponentType.Document, "",

0 commit comments

Comments
 (0)