Skip to content

Commit 8a368f3

Browse files
committed
Add SuspiciousLetAssignmentInspection
1 parent d70d3cb commit 8a368f3

File tree

11 files changed

+404
-0
lines changed

11 files changed

+404
-0
lines changed
Lines changed: 180 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,180 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Inspections.Extensions;
5+
using Rubberduck.Inspections.Results;
6+
using Rubberduck.Parsing;
7+
using Rubberduck.Parsing.Grammar;
8+
using Rubberduck.Parsing.Inspections;
9+
using Rubberduck.Parsing.Inspections.Abstract;
10+
using Rubberduck.Parsing.Symbols;
11+
using Rubberduck.Parsing.VBA;
12+
using Rubberduck.Parsing.VBA.DeclarationCaching;
13+
using Rubberduck.Resources.Inspections;
14+
using Rubberduck.VBEditor;
15+
16+
namespace Rubberduck.Inspections.Concrete
17+
{
18+
/// <summary>
19+
/// Identifies assignments without Set for which both sides are objects.
20+
/// </summary>
21+
/// <why>
22+
/// Whenever both sides of an assignment without Set are objects, there is an assignment from the default member of the RHS to the one on the LHS.
23+
/// Although this might be intentional, in many situations it will just mask an erroneously forgotten Set.
24+
/// </why>
25+
/// <example hasResult="true">
26+
/// <![CDATA[
27+
/// Public Sub DoSomething(ByVal rng As Excel.Range, ByVal arg As ADODB Field)
28+
/// rng = arg
29+
/// End Sub
30+
/// ]]>
31+
/// </example>
32+
/// <example hasResult="false">
33+
/// <![CDATA[
34+
/// Public Sub DoSomething(ByVal rng As Excel.Range, ByVal arg As ADODB Field)
35+
/// rng.Value = arg.Value
36+
/// End Sub
37+
/// ]]>
38+
/// </example>
39+
/// <example hasResult="false">
40+
/// <![CDATA[
41+
/// Public Sub DoSomething(ByVal rng As Excel.Range, ByVal arg As ADODB Field)
42+
/// Let rng = arg
43+
/// End Sub
44+
/// ]]>
45+
/// </example>
46+
public sealed class SuspiciousLetAssignmentInspection : InspectionBase
47+
{
48+
private readonly IDeclarationFinderProvider _declarationFinderProvider;
49+
50+
public SuspiciousLetAssignmentInspection(RubberduckParserState state)
51+
: base(state)
52+
{
53+
_declarationFinderProvider = state;
54+
Severity = CodeInspectionSeverity.Warning;
55+
}
56+
57+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
58+
{
59+
var results = new List<IInspectionResult>();
60+
foreach (var moduleDeclaration in State.DeclarationFinder.UserDeclarations(DeclarationType.Module))
61+
{
62+
if (moduleDeclaration == null || moduleDeclaration.IsIgnoringInspectionResultFor(AnnotationName))
63+
{
64+
continue;
65+
}
66+
67+
var module = moduleDeclaration.QualifiedModuleName;
68+
results.AddRange(DoGetInspectionResults(module));
69+
}
70+
71+
return results;
72+
}
73+
74+
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
75+
{
76+
var finder = _declarationFinderProvider.DeclarationFinder;
77+
return BoundLhsInspectionResults(module, finder)
78+
.Concat(UnboundLhsInspectionResults(module, finder));
79+
}
80+
81+
private IEnumerable<IInspectionResult> BoundLhsInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
82+
{
83+
var implicitDefaultMemberAssignments = finder
84+
.IdentifierReferences(module)
85+
.Where(IsImplicitDefaultMemberAssignment)
86+
.ToList();
87+
88+
var results = new List<IInspectionResult>();
89+
foreach (var assignment in implicitDefaultMemberAssignments)
90+
{
91+
var (rhsDefaultMemberAccess, isUnbound) = RhsImplicitDefaultMemberAccess(assignment, finder);
92+
93+
if (rhsDefaultMemberAccess != null)
94+
{
95+
var result = InspectionResult(assignment, rhsDefaultMemberAccess, isUnbound, _declarationFinderProvider);
96+
results.Add(result);
97+
}
98+
}
99+
100+
return results;
101+
}
102+
103+
private bool IsImplicitDefaultMemberAssignment(IdentifierReference reference)
104+
{
105+
return reference.IsNonIndexedDefaultMemberAccess
106+
&& reference.IsAssignment
107+
&& !reference.IsSetAssignment
108+
&& !reference.HasExplicitLetStatement
109+
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
110+
}
111+
112+
private (IdentifierReference identifierReference, bool isUnbound) RhsImplicitDefaultMemberAccess(IdentifierReference assignment, DeclarationFinder finder)
113+
{
114+
if (!(assignment.Context.Parent is VBAParser.LetStmtContext letStatement))
115+
{
116+
return (null, false);
117+
}
118+
119+
var rhsSelection = new QualifiedSelection(assignment.QualifiedModuleName, letStatement.expression().GetSelection());
120+
121+
var boundRhsDefaultMemberAccess = finder.IdentifierReferences(rhsSelection)
122+
.FirstOrDefault(reference => reference.IsNonIndexedDefaultMemberAccess
123+
&& !reference.IsInnerRecursiveDefaultMemberAccess);
124+
if (boundRhsDefaultMemberAccess != null)
125+
{
126+
return (boundRhsDefaultMemberAccess, false);
127+
}
128+
129+
var unboundRhsDefaultMemberAccess = finder.UnboundDefaultMemberAccesses(rhsSelection.QualifiedName)
130+
.FirstOrDefault(reference => reference.IsNonIndexedDefaultMemberAccess
131+
&& !reference.IsInnerRecursiveDefaultMemberAccess
132+
&& reference.Selection.Equals(rhsSelection.Selection));
133+
return (unboundRhsDefaultMemberAccess, true);
134+
}
135+
136+
private IInspectionResult InspectionResult(IdentifierReference lhsReference, IdentifierReference rhsReference, bool isUnbound, IDeclarationFinderProvider declarationFinderProvider)
137+
{
138+
var result = new IdentifierReferenceInspectionResult(
139+
this,
140+
ResultDescription(lhsReference, rhsReference),
141+
declarationFinderProvider,
142+
lhsReference);
143+
result.Properties.RhSReference = rhsReference;
144+
if (isUnbound)
145+
{
146+
result.Properties.DisableFixes = "ExpandDefaultMemberQuickFix";
147+
}
148+
149+
return result;
150+
}
151+
152+
private string ResultDescription(IdentifierReference lhsReference, IdentifierReference rhsReference)
153+
{
154+
var lhsExpression = lhsReference.IdentifierName;
155+
var rhsExpression = rhsReference.IdentifierName;
156+
return string.Format(InspectionResults.SuspiciousLetAssignmentInspection, lhsExpression, rhsExpression);
157+
}
158+
159+
private IEnumerable<IInspectionResult> UnboundLhsInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
160+
{
161+
var implicitDefaultMemberAssignments = finder
162+
.UnboundDefaultMemberAccesses(module)
163+
.Where(IsImplicitDefaultMemberAssignment);
164+
165+
var results = new List<IInspectionResult>();
166+
foreach (var assignment in implicitDefaultMemberAssignments)
167+
{
168+
var (rhsDefaultMemberAccess, isUnbound) = RhsImplicitDefaultMemberAccess(assignment, finder);
169+
170+
if (rhsDefaultMemberAccess != null)
171+
{
172+
var result = InspectionResult(assignment, rhsDefaultMemberAccess, true, _declarationFinderProvider);
173+
results.Add(result);
174+
}
175+
}
176+
177+
return results;
178+
}
179+
}
180+
}

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
@@ -427,4 +427,7 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
427427
<data name="ImplicitUnboundDefaultMemberAccessInspection" xml:space="preserve">
428428
<value>Zugriffe auf Standardmember verstecken, welcher Member aufgerufen wird. Dies ist besonders verwirrend, wenn in dem Ausdruck selber keine Indikation vorhanden ist, dass ein solcher Zugriff erfolgt, und zudem der Standardmember erst zur Laufzeit ermittelt werden kann. Dies kann dazu führen, dass Fehler durch vergessene Memberaufrufe nicht erkannt werden. Sollte weiterhin zur Laufzeit kein Standardmember auf dem Objekt existsieren, so kommt es zu einem Fehler 438 'Objekt unterstützt diese Eigenschaft oder Methode nicht'.</value>
429429
</data>
430+
<data name="SuspiciousLetAssignmentInspection" xml:space="preserve">
431+
<value>Wenn beide Seiten einer Zuweisung ohne Set Objekte sind, kommt es zu einer Zuweisung vom Standardmember der rechten Seite zu dem der linken. Auch wenn dies manchmal beabsichtigt sein kann, kann es in vielen Fällen dazu führen, dass nicht bemerkt wird, dass Set fehlerhafter Weise vergessen wurde.</value>
432+
</data>
430433
</root>

Rubberduck.Resources/Inspections/InspectionInfo.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -430,4 +430,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu
430430
<data name="ImplicitUnboundDefaultMemberAccessInspection" xml:space="preserve">
431431
<value>Default member accesses hide away the actually called member. This is especially misleading if there is no indication in the expression that such a call is made and if the default member cannot be determined from the declared type of the object. As a consequence, errors in which a member was forgotten to be called can go unnoticed and should there not be a suitable default member at runtime, an error 438 'Object doesn't support this property or method' will be raised.</value>
432432
</data>
433+
<data name="SuspiciousLetAssignmentInspection" xml:space="preserve">
434+
<value>Whenever both sides of an assignment without Set are objects, there is an assignment from the default member of the RHS to the one on the LHS. Although this might be intentional, in many situations it will just mask an erroneously forgotten Set.</value>
435+
</data>
433436
</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
@@ -414,4 +414,7 @@
414414
<data name="ImplicitUnboundDefaultMemberAccessInspection" xml:space="preserve">
415415
<value>Impliziter nicht gebundener Zugriff auf einen Standardmember</value>
416416
</data>
417+
<data name="SuspiciousLetAssignmentInspection" xml:space="preserve">
418+
<value>Verdächtige Let-Zuweisung</value>
419+
</data>
417420
</root>

Rubberduck.Resources/Inspections/InspectionNames.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -434,4 +434,7 @@
434434
<data name="ImplicitUnboundDefaultMemberAccessInspection" xml:space="preserve">
435435
<value>Implicit unbound default member access</value>
436436
</data>
437+
<data name="SuspiciousLetAssignmentInspection" xml:space="preserve">
438+
<value>Suspicious Let assignment</value>
439+
</data>
437440
</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
@@ -437,4 +437,7 @@ In Memoriam, 1972-2018</value>
437437
<data name="ImplicitUnboundDefaultMemberAccessInspection" xml:space="preserve">
438438
<value>Für den Ausdruck '{0}' kommt es zu einem impliziten nicht gebundenen Standardmemberzugriff.</value>
439439
</data>
440+
<data name="SuspiciousLetAssignmentInspection" xml:space="preserve">
441+
<value>Es wird vom Standardmember des Resultats des Ausdrucks '{1}' dem des Resultats des Ausdrucks '{0}' zugewiesen.</value>
442+
</data>
440443
</root>

Rubberduck.Resources/Inspections/InspectionResults.resx

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -494,4 +494,8 @@ In memoriam, 1972-2018</value>
494494
<value>On the expression '{0}', there is an implicit unbound default member access.</value>
495495
<comment>{0} expression</comment>
496496
</data>
497+
<data name="SuspiciousLetAssignmentInspection" xml:space="preserve">
498+
<value>There is an assignment from the default member of the result of expression '{1}' to that of the expression '{0}'.</value>
499+
<comment>{0} lhsExpression; {1} rhsExpression</comment>
500+
</data>
497501
</root>

0 commit comments

Comments
 (0)