Skip to content

Commit 95e9513

Browse files
authored
Merge pull request #5167 from MDoerner/SuspiciousLetAssignmentInspection
Suspicious Let assignment inspection
2 parents acdf44e + c0c83e4 commit 95e9513

20 files changed

+558
-28
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.CodeAnalysis/QuickFixes/ExpandDefaultMemberQuickFix.cs

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using Rubberduck.Inspections.Concrete;
55
using Rubberduck.Parsing.Inspections.Abstract;
66
using Rubberduck.Parsing.Rewriter;
7+
using Rubberduck.Parsing.Symbols;
78
using Rubberduck.Parsing.VBA;
89
using Rubberduck.Parsing.VBA.DeclarationCaching;
910
using Rubberduck.VBEditor;
@@ -20,7 +21,8 @@ public ExpandDefaultMemberQuickFix(IDeclarationFinderProvider declarationFinderP
2021
typeof(IndexedDefaultMemberAccessInspection),
2122
typeof(IndexedRecursiveDefaultMemberAccessInspection),
2223
typeof(ImplicitDefaultMemberAccessInspection),
23-
typeof(ImplicitRecursiveDefaultMemberAccessInspection))
24+
typeof(ImplicitRecursiveDefaultMemberAccessInspection),
25+
typeof(SuspiciousLetAssignmentInspection))
2426
{
2527
_declarationFinderProvider = declarationFinderProvider;
2628
}
@@ -33,6 +35,14 @@ public override void Fix(IInspectionResult result, IRewriteSession rewriteSessio
3335
var lExpressionContext = result.Context;
3436
var selection = result.QualifiedSelection;
3537
InsertDefaultMember(lExpressionContext, selection, finder, rewriter);
38+
39+
if (result.Inspection is SuspiciousLetAssignmentInspection)
40+
{
41+
IdentifierReference rhsReference = result.Properties.RhSReference;
42+
var rhsLExpressionContext = rhsReference.Context;
43+
var rhsSelection = rhsReference.QualifiedSelection;
44+
InsertDefaultMember(rhsLExpressionContext, rhsSelection, finder, rewriter);
45+
}
3646
}
3747

3848
private void InsertDefaultMember(ParserRuleContext lExpressionContext, QualifiedSelection selection, DeclarationFinder finder, IModuleRewriter rewriter)

Rubberduck.CodeAnalysis/QuickFixes/UseSetKeywordForObjectAssignmentQuickFix.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ namespace Rubberduck.Inspections.QuickFixes
1010
public sealed class UseSetKeywordForObjectAssignmentQuickFix : QuickFixBase
1111
{
1212
public UseSetKeywordForObjectAssignmentQuickFix()
13-
: base(typeof(ObjectVariableNotSetInspection))
13+
: base(typeof(ObjectVariableNotSetInspection), typeof(SuspiciousLetAssignmentInspection))
1414
{}
1515

1616
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)

Rubberduck.Parsing/Binding/Bindings/IndexDefaultBinding.cs

Lines changed: 10 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -298,14 +298,21 @@ private IBoundExpression ResolveDefaultMember(string asTypeName, Declaration asT
298298
named arguments. In this case, the index expression is classified as an unbound member with
299299
a declared type of Variant, referencing <l-expression> with no member name.
300300
*/
301-
if (
302-
(Tokens.Variant.Equals(asTypeName, StringComparison.InvariantCultureIgnoreCase)
303-
|| Tokens.Object.Equals(asTypeName, StringComparison.InvariantCultureIgnoreCase))
301+
if (Tokens.Variant.Equals(asTypeName, StringComparison.InvariantCultureIgnoreCase)
302+
&& !argumentList.HasNamedArguments)
303+
{
304+
ResolveArgumentList(null, argumentList);
305+
//We do not treat unbound accesses on variables of type Variant as default member accesses because they could be array accesses as well.
306+
return new IndexExpression(null, ExpressionClassification.Unbound, expression, _lExpression, argumentList, isDefaultMemberAccess: false, defaultMemberRecursionDepth: defaultMemberResolutionRecursionDepth, containedDefaultMemberRecursionExpression: containedExpression);
307+
}
308+
309+
if (Tokens.Object.Equals(asTypeName, StringComparison.InvariantCultureIgnoreCase)
304310
&& !argumentList.HasNamedArguments)
305311
{
306312
ResolveArgumentList(null, argumentList);
307313
return new IndexExpression(null, ExpressionClassification.Unbound, expression, _lExpression, argumentList, isDefaultMemberAccess: true, defaultMemberRecursionDepth: defaultMemberResolutionRecursionDepth, containedDefaultMemberRecursionExpression: containedExpression);
308314
}
315+
309316
/*
310317
The declared type of <l-expression> is a specific class, which has a public default Property
311318
Get, Property Let, function or subroutine, and one of the following is true:

Rubberduck.Parsing/Symbols/IdentifierReference.cs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -33,9 +33,8 @@ public IdentifierReference(
3333
{
3434
ParentScoping = parentScopingDeclaration;
3535
ParentNonScoping = parentNonScopingDeclaration;
36-
QualifiedModuleName = qualifiedName;
36+
QualifiedSelection = new QualifiedSelection(qualifiedName, selection);
3737
IdentifierName = identifierName;
38-
Selection = selection;
3938
Context = context;
4039
Declaration = declaration;
4140
HasExplicitLetStatement = hasExplicitLetStatement;
@@ -50,12 +49,12 @@ public IdentifierReference(
5049
IsInnerRecursiveDefaultMemberAccess = isInnerRecursiveDefaultMemberAccess;
5150
}
5251

53-
public QualifiedModuleName QualifiedModuleName { get; }
52+
public QualifiedSelection QualifiedSelection { get; }
53+
public QualifiedModuleName QualifiedModuleName => QualifiedSelection.QualifiedName;
54+
public Selection Selection => QualifiedSelection.Selection;
5455

5556
public string IdentifierName { get; }
5657

57-
public Selection Selection { get; }
58-
5958
/// <summary>
6059
/// Gets the scoping <see cref="Declaration"/> that contains this identifier reference,
6160
/// e.g. a module, procedure, function or property.

Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -250,6 +250,11 @@ private void Visit(
250250
Visit(expression.LExpression, module, scope, parent, hasExplicitLetStatement: hasExplicitLetStatement);
251251
AddArrayAccessReference(expression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement, isSetAssignment);
252252
}
253+
else if (expression.Classification == ExpressionClassification.Unbound
254+
&& expression.ReferencedDeclaration == null)
255+
{
256+
Visit(expression.LExpression, module, scope, parent);
257+
}
253258
else
254259
{
255260
// Index expressions are a bit special in that they can refer to parameterized properties and functions.

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.

0 commit comments

Comments
 (0)