Skip to content

Commit b267817

Browse files
committed
Add UseOfBangNotationInspection
1 parent d027edf commit b267817

File tree

12 files changed

+502
-9
lines changed

12 files changed

+502
-9
lines changed
Lines changed: 115 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,115 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing.Inspections.Abstract;
6+
using Rubberduck.Resources.Inspections;
7+
using Rubberduck.Parsing.Symbols;
8+
using Rubberduck.Parsing.VBA;
9+
using Rubberduck.Inspections.Inspections.Extensions;
10+
using Rubberduck.Parsing.Grammar;
11+
using Rubberduck.VBEditor;
12+
13+
namespace Rubberduck.Inspections.Concrete
14+
{
15+
/// <summary>
16+
/// Identifies the use of bang notation, formally known as dictionary access expression.
17+
/// </summary>
18+
/// <why>
19+
/// A dictionary access expression looks like a strongly typed call, but it actually is a stringly typed access to the parameterized default member of the object.
20+
/// </why>
21+
/// <example hasResult="true">
22+
/// <![CDATA[
23+
/// Public Sub DoSomething(ByVal wkb As Excel.Workbook)
24+
/// wkb.Worksheets!MySheet.Range("A1").Value = 42
25+
/// End Sub
26+
/// ]]>
27+
/// </example>
28+
/// <example hasResult="true">
29+
/// <![CDATA[
30+
/// Public Sub DoSomething(ByVal wkb As Excel.Workbook)
31+
/// With wkb.Worksheets
32+
/// !MySheet.Range("A1").Value = 42
33+
/// End With
34+
/// End Sub
35+
/// ]]>
36+
/// </example>
37+
/// <example hasResult="false">
38+
/// <![CDATA[
39+
/// Public Sub DoSomething(ByVal wkb As Excel.Workbook)
40+
/// wkb.Worksheets("MySheet").Range("A1").Value = 42
41+
/// End Sub
42+
/// ]]>
43+
/// </example>
44+
/// <example hasResult="false">
45+
/// <![CDATA[
46+
/// Public Sub DoSomething(ByVal wkb As Excel.Workbook)
47+
/// wkb.Worksheets.Item("MySheet").Range("A1").Value = 42
48+
/// End Sub
49+
/// ]]>
50+
/// </example>
51+
/// <example hasResult="false">
52+
/// <![CDATA[
53+
/// Public Sub DoSomething(ByVal wkb As Excel.Workbook)
54+
/// With wkb.Worksheets
55+
/// .Item("MySheet").Range("A1").Value = 42
56+
/// End With
57+
/// End Sub
58+
/// ]]>
59+
/// </example>
60+
public sealed class UseOfBangNotationInspection : InspectionBase
61+
{
62+
public UseOfBangNotationInspection(RubberduckParserState state)
63+
: base(state) { }
64+
65+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
66+
{
67+
var results = new List<IInspectionResult>();
68+
foreach (var moduleDeclaration in State.DeclarationFinder.UserDeclarations(DeclarationType.Module))
69+
{
70+
if (moduleDeclaration == null || moduleDeclaration.IsIgnoringInspectionResultFor(AnnotationName))
71+
{
72+
continue;
73+
}
74+
75+
var module = moduleDeclaration.QualifiedModuleName;
76+
results.AddRange(DoGetInspectionResults(module));
77+
}
78+
79+
return results;
80+
}
81+
82+
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
83+
{
84+
var usesOfBang = State.DeclarationFinder
85+
.IdentifierReferences(module)
86+
.Where(IsRelevantReference);
87+
88+
return usesOfBang
89+
.Select(useOfBang => InspectionResult(useOfBang, State))
90+
.ToList();
91+
}
92+
93+
private bool IsRelevantReference(IdentifierReference reference)
94+
{
95+
return reference.IsIndexedDefaultMemberAccess
96+
&& reference.DefaultMemberRecursionDepth == 1
97+
&& reference.Context is VBAParser.DictionaryAccessContext
98+
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
99+
}
100+
101+
private IInspectionResult InspectionResult(IdentifierReference dictionaryAccess, IDeclarationFinderProvider declarationFinderProvider)
102+
{
103+
return new IdentifierReferenceInspectionResult(this,
104+
ResultDescription(dictionaryAccess),
105+
declarationFinderProvider,
106+
dictionaryAccess);
107+
}
108+
109+
private string ResultDescription(IdentifierReference dictionaryAccess)
110+
{
111+
var expression = dictionaryAccess.IdentifierName;
112+
return string.Format(InspectionResults.UseOfBangNotationInspection, expression);
113+
}
114+
}
115+
}

Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs

Lines changed: 13 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -118,15 +118,16 @@ private void Visit(
118118
var callSiteContext = expression.Context;
119119
var identifier = expression.Context.GetText();
120120
var callee = expression.ReferencedDeclaration;
121+
var selection = callSiteContext.GetSelection();
121122
expression.ReferencedDeclaration.AddReference(
122123
module,
123124
scope,
124125
parent,
125126
callSiteContext,
126127
identifier,
127128
callee,
128-
callSiteContext.GetSelection(),
129-
FindIdentifierAnnotations(module, callSiteContext.GetSelection().StartLine),
129+
selection,
130+
FindIdentifierAnnotations(module, selection.StartLine),
130131
isAssignmentTarget,
131132
hasExplicitLetStatement,
132133
isSetAssignment);
@@ -157,15 +158,16 @@ private void Visit(
157158
var callSiteContext = expression.UnrestrictedNameContext;
158159
var identifier = expression.UnrestrictedNameContext.GetText();
159160
var callee = expression.ReferencedDeclaration;
161+
var selection = callSiteContext.GetSelection();
160162
expression.ReferencedDeclaration.AddReference(
161163
module,
162164
scope,
163165
parent,
164166
callSiteContext,
165167
identifier,
166168
callee,
167-
callSiteContext.GetSelection(),
168-
FindIdentifierAnnotations(module, callSiteContext.GetSelection().StartLine),
169+
selection,
170+
FindIdentifierAnnotations(module, selection.StartLine),
169171
isAssignmentTarget,
170172
hasExplicitLetStatement,
171173
isSetAssignment);
@@ -712,17 +714,18 @@ private void AddDefaultMemberReference(
712714
bool isSetAssignment)
713715
{
714716
var callSiteContext = expression.DefaultMemberContext;
715-
var identifier = expression.ReferencedDeclaration.IdentifierName;
717+
var identifier = expression.Context.GetText();
716718
var callee = expression.ReferencedDeclaration;
719+
var selection = callSiteContext.GetSelection();
717720
expression.ReferencedDeclaration.AddReference(
718721
module,
719722
scope,
720723
parent,
721724
callSiteContext,
722725
identifier,
723726
callee,
724-
callSiteContext.GetSelection(),
725-
FindIdentifierAnnotations(module, callSiteContext.GetSelection().StartLine),
727+
selection,
728+
FindIdentifierAnnotations(module, selection.StartLine),
726729
isAssignmentTarget,
727730
hasExplicitLetStatement,
728731
isSetAssignment,
@@ -847,6 +850,7 @@ private void Visit(
847850
{
848851
var callSiteContext = expression.Context;
849852
var identifier = expression.Context.GetText();
853+
var selection = callSiteContext.GetSelection();
850854
var callee = expression.ReferencedDeclaration;
851855
expression.ReferencedDeclaration.AddReference(
852856
module,
@@ -855,8 +859,8 @@ private void Visit(
855859
callSiteContext,
856860
identifier,
857861
callee,
858-
callSiteContext.GetSelection(),
859-
FindIdentifierAnnotations(module, callSiteContext.GetSelection().StartLine),
862+
selection,
863+
FindIdentifierAnnotations(module, selection.StartLine),
860864
isAssignmentTarget,
861865
hasExplicitLetStatement,
862866
isSetAssignment);

Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs

Lines changed: 9 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Resources/Inspections/InspectionInfo.de.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -403,4 +403,7 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
403403
<data name="DefaultMemberRequiredInspection" xml:space="preserve">
404404
<value>Der VBA-Compiler gibt keinen Fehler aus, wenn ein Standardmemberzugriff nötig ist, aber der der deklarierte Type des Objekts keinen passenden Standardmember hat. In fast allen Fällen führt dies zu einem Laufzeitfehler91 'Objektvariable oder With-Blockvariable nicht festgelegt' oder 438 'Objekt unterstützt diese Eigenschaft oder Methode nicht' abhängig davon, ob die Variable den Wert 'Nothing' hat oder nicht, der schwerer zu entdecken ist und auf einen Programmierfehler hinweist.</value>
405405
</data>
406+
<data name="UseOfBangNotationInspection" xml:space="preserve">
407+
<value>Die Ausrufezeichennotation erweckt den Eindruck, dass es sich um einen Zugriff handelt, der Typchecks unterliegt. Allerdings handelt es sich lediglich um einen Zugriff auf den Standardmember des Objekts, auf das sie angewendent wird, bei dem das Argument als Zeichenkette übergeben wird.</value>
408+
</data>
406409
</root>

Rubberduck.Resources/Inspections/InspectionInfo.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -403,4 +403,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu
403403
<data name="DefaultMemberRequiredInspection" xml:space="preserve">
404404
<value>The VBA compiler does not raise an error if an indexed default member call is required but the object's declared type does not have a suitable default member. Under almost all circumstances, this leads to a run-time error 91 'Object or With block variable not set' or 438 'Object doesn't support this property or method' depending on whether the object has the value 'Nothing' or not, which is harder to detect and indicates a bug.</value>
405405
</data>
406+
<data name="UseOfBangNotationInspection" xml:space="preserve">
407+
<value>Bang notation, formally known as dictionary access expression, looks like it is strongly typed. However, it is actually a stringly typed access to the paramterized default member of the object it is used on.</value>
408+
</data>
406409
</root>

Rubberduck.Resources/Inspections/InspectionNames.Designer.cs

Lines changed: 9 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Resources/Inspections/InspectionNames.de.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -387,4 +387,7 @@
387387
<data name="DefaultMemberRequiredInspection" xml:space="preserve">
388388
<value>Standardmemberzugriff ohne Standardmember</value>
389389
</data>
390+
<data name="UseOfBangNotationInspection" xml:space="preserve">
391+
<value>Verwendung der Ausrufezeichennotation</value>
392+
</data>
390393
</root>

Rubberduck.Resources/Inspections/InspectionNames.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -407,4 +407,7 @@
407407
<data name="DefaultMemberRequiredInspection" xml:space="preserve">
408408
<value>Indexed default member access without default member</value>
409409
</data>
410+
<data name="UseOfBangNotationInspection" xml:space="preserve">
411+
<value>Use of bang notation</value>
412+
</data>
410413
</root>

Rubberduck.Resources/Inspections/InspectionResults.Designer.cs

Lines changed: 9 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Resources/Inspections/InspectionResults.de.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -428,4 +428,7 @@ In Memoriam, 1972-2018</value>
428428
<data name="DefaultMemberRequiredInspection" xml:space="preserve">
429429
<value>Der Ausdruck '{0}' erfordert einen Standardmemberzugriff, aber der Typ '{1}' hat keinen passenden Standardmember.</value>
430430
</data>
431+
<data name="UseOfBangNotationInspection" xml:space="preserve">
432+
<value>Der Ausdruck '{0}' verwendet Ausrufezeichennotation.</value>
433+
</data>
431434
</root>

0 commit comments

Comments
 (0)