Skip to content

Commit 53518af

Browse files
authored
Merge pull request #3719 from retailcoder/next
Fixes ObjectVariableNotSet false positives
2 parents bfc6720 + 46e9817 commit 53518af

26 files changed

+341
-331
lines changed

RetailCoder.VBE/UI/RubberduckUI.resx

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -381,15 +381,6 @@ Warning: All customized settings will be lost. Your old file will be saved in '
381381
<data name="Rubberduck_AboutBuild" xml:space="preserve">
382382
<value>Version {0}</value>
383383
</data>
384-
<data name="TodoMarkerBug" xml:space="preserve">
385-
<value>BUG</value>
386-
</data>
387-
<data name="TodoMarkerNote" xml:space="preserve">
388-
<value>NOTE</value>
389-
</data>
390-
<data name="TodoMarkerTodo" xml:space="preserve">
391-
<value>TODO</value>
392-
</data>
393384
<data name="AllImplementations_Caption" xml:space="preserve">
394385
<value>Implementations of '{0}'</value>
395386
</data>
Lines changed: 25 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,12 @@
1-
using System;
2-
using System.Collections.Generic;
1+
using System.Collections.Generic;
32
using System.Linq;
43
using Rubberduck.Inspections.Abstract;
54
using Rubberduck.Inspections.Results;
6-
using Rubberduck.Parsing;
7-
using Rubberduck.Parsing.Grammar;
85
using Rubberduck.Parsing.Inspections.Abstract;
96
using Rubberduck.Parsing.Inspections.Resources;
107
using Rubberduck.Parsing.Symbols;
118
using Rubberduck.Parsing.VBA;
9+
using Rubberduck.VBEditor.SafeComWrappers;
1210

1311
namespace Rubberduck.Inspections.Concrete
1412
{
@@ -21,34 +19,36 @@ public ObjectVariableNotSetInspection(RubberduckParserState state)
2119

2220
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2321
{
24-
var allInterestingDeclarations =
25-
VariableRequiresSetAssignmentEvaluator.GetDeclarationsPotentiallyRequiringSetAssignment(State.AllUserDeclarations);
2622

27-
var candidateReferencesRequiringSetAssignment =
28-
allInterestingDeclarations
29-
.SelectMany(dec => dec.References)
30-
.Where(reference => !IsIgnoringInspectionResultFor(reference, AnnotationName))
31-
.Where(reference => reference.IsAssignment);
32-
33-
var referencesRequiringSetAssignment = candidateReferencesRequiringSetAssignment
34-
.Where(reference => VariableRequiresSetAssignmentEvaluator.RequiresSetAssignment(reference, State));
35-
36-
var objectVariableNotSetReferences = referencesRequiringSetAssignment.Where(FlagIfObjectVariableNotSet);
37-
38-
return objectVariableNotSetReferences
39-
.Select(reference =>
23+
return InterestingReferences().Select(reference =>
4024
new IdentifierReferenceInspectionResult(this,
4125
string.Format(InspectionsUI.ObjectVariableNotSetInspectionResultFormat, reference.Declaration.IdentifierName),
4226
State, reference));
4327
}
4428

45-
private bool FlagIfObjectVariableNotSet(IdentifierReference reference)
29+
private IEnumerable<IdentifierReference> InterestingReferences()
4630
{
47-
var allrefs = reference.Declaration.References;
48-
var letStmtContext = reference.Context.GetAncestor<VBAParser.LetStmtContext>();
49-
50-
return reference.IsAssignment && (letStmtContext != null
51-
|| allrefs.Where(r => r.IsAssignment).All(r => r.Context.GetAncestor<VBAParser.SetStmtContext>()?.expression()?.GetText().Equals(Tokens.Nothing, StringComparison.InvariantCultureIgnoreCase) ?? false));
31+
var result = new List<IdentifierReference>();
32+
foreach (var moduleReferences in State.DeclarationFinder.IdentifierReferences())
33+
{
34+
var module = State.DeclarationFinder.ModuleDeclaration(moduleReferences.Key);
35+
if (module == null || !module.IsUserDefined || IsIgnoringInspectionResultFor(module, AnnotationName))
36+
{
37+
// module isn't user code (?), or this inspection is ignored at module-level
38+
continue;
39+
}
40+
41+
foreach (var reference in moduleReferences.Value)
42+
{
43+
if (!IsIgnoringInspectionResultFor(reference, AnnotationName)
44+
&& VariableRequiresSetAssignmentEvaluator.NeedsSetKeywordAdded(reference, State))
45+
{
46+
result.Add(reference);
47+
}
48+
}
49+
}
50+
51+
return result;
5252
}
5353
}
5454
}

Rubberduck.Inspections/QuickFixes/AssignedByValParameterMakeLocalCopyQuickFix.cs

Lines changed: 5 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -116,21 +116,17 @@ private void InsertLocalVariableDeclarationAndAssignment(IModuleRewriter rewrite
116116
var requiresAssignmentUsingSet =
117117
target.References.Any(refItem => VariableRequiresSetAssignmentEvaluator.RequiresSetAssignment(refItem, _parserState));
118118

119-
var localVariableAssignment = string.Format("{0}{1}",
120-
requiresAssignmentUsingSet ? $"{Tokens.Set} " : string.Empty,
121-
$"{localIdentifier} = {target.IdentifierName}");
119+
var localVariableAssignment =
120+
$"{(requiresAssignmentUsingSet ? $"{Tokens.Set} " : string.Empty)}{localIdentifier} = {target.IdentifierName}";
122121

123122
var endOfStmtCtxt = ((ParserRuleContext)target.Context.Parent.Parent).GetChild<VBAParser.EndOfStatementContext>();
124123
var eosContent = endOfStmtCtxt.GetText();
125-
var idxLastNewLine = eosContent.LastIndexOf(Environment.NewLine);
124+
var idxLastNewLine = eosContent.LastIndexOf(Environment.NewLine, StringComparison.InvariantCultureIgnoreCase);
126125
var endOfStmtCtxtComment = eosContent.Substring(0, idxLastNewLine);
127126
var endOfStmtCtxtEndFormat = eosContent.Substring(idxLastNewLine);
128127

129-
var insertCtxt = (ParserRuleContext)((ParserRuleContext)target.Context.Parent.Parent).GetChild<VBAParser.AsTypeClauseContext>();
130-
if (insertCtxt == null)
131-
{
132-
insertCtxt = (ParserRuleContext)target.Context.Parent;
133-
}
128+
var insertCtxt = ((ParserRuleContext) target.Context.Parent.Parent).GetChild<VBAParser.AsTypeClauseContext>()
129+
?? (ParserRuleContext) target.Context.Parent;
134130

135131
rewriter.Remove(endOfStmtCtxt);
136132
rewriter.InsertAfter(insertCtxt.Stop.TokenIndex, $"{endOfStmtCtxtComment}{endOfStmtCtxtEndFormat}{localVariableDeclaration}" + $"{endOfStmtCtxtEndFormat}{localVariableAssignment}{endOfStmtCtxtEndFormat}");

Rubberduck.Inspections/VariableRequiresSetAssignmentEvaluator.cs

Lines changed: 103 additions & 94 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
using Rubberduck.Parsing.Symbols;
44
using Rubberduck.Parsing.VBA;
55
using System.Collections.Generic;
6+
using System.Diagnostics;
67
using System.Linq;
78

89
namespace Rubberduck.Inspections
@@ -19,39 +20,126 @@ public static IEnumerable<Declaration> GetDeclarationsPotentiallyRequiringSetAss
1920
return relevantDeclarations;
2021
}
2122

23+
/// <summary>
24+
/// Determines whether the 'Set' keyword needs to be added in the context of the specified identifier reference.
25+
/// </summary>
26+
/// <param name="reference">The identifier reference to analyze</param>
27+
/// <param name="state">The parser state</param>
28+
public static bool NeedsSetKeywordAdded(IdentifierReference reference, RubberduckParserState state)
29+
{
30+
var setStmtContext = reference.Context.GetAncestor<VBAParser.SetStmtContext>();
31+
return setStmtContext == null && RequiresSetAssignment(reference, state);
32+
}
33+
34+
/// <summary>
35+
/// Determines whether the 'Set' keyword is required (whether it's present or not) for the specified identifier reference.
36+
/// </summary>
37+
/// <param name="reference">The identifier reference to analyze</param>
38+
/// <param name="state">The parser state</param>
2239
public static bool RequiresSetAssignment(IdentifierReference reference, RubberduckParserState state)
2340
{
24-
//Not an assignment...definitely does not require a 'Set' assignment
2541
if (!reference.IsAssignment)
2642
{
43+
// reference isn't assigning its declaration; not interesting
44+
return false;
45+
}
46+
47+
var setStmtContext = reference.Context.GetAncestor<VBAParser.SetStmtContext>();
48+
if (setStmtContext != null)
49+
{
50+
// don't assume Set keyword is legit...
51+
return reference.Declaration.IsObject;
52+
}
53+
54+
var letStmtContext = reference.Context.GetAncestor<VBAParser.LetStmtContext>();
55+
if (letStmtContext == null)
56+
{
57+
// not an assignment
2758
return false;
2859
}
29-
30-
//We know for sure it DOES NOT use 'Set'
31-
if (!MayRequireAssignmentUsingSet(reference.Declaration))
60+
61+
var declaration = reference.Declaration;
62+
if (declaration.IsArray)
63+
{
64+
// arrays don't need a Set statement... todo figure out if array items are objects
65+
return false;
66+
}
67+
68+
var isObjectVariable = declaration.IsObject;
69+
var isVariant = declaration.IsUndeclared || declaration.AsTypeName == Tokens.Variant;
70+
if (!isObjectVariable && !isVariant)
3271
{
3372
return false;
3473
}
3574

36-
//We know for sure that it DOES use 'Set'
37-
if (RequiresAssignmentUsingSet(reference.Declaration))
75+
if (isObjectVariable)
3876
{
77+
// get the members of the returning type, a default member could make us lie otherwise
78+
var classModule = declaration.AsTypeDeclaration as ClassModuleDeclaration;
79+
if (classModule?.DefaultMember != null)
80+
{
81+
var parameters = (classModule.DefaultMember as IParameterizedDeclaration)?.Parameters.ToArray() ?? Enumerable.Empty<ParameterDeclaration>().ToArray();
82+
if (!parameters.Any() || parameters.All(p => p.IsOptional))
83+
{
84+
// assigned declaration has a default parameterless member, which is legally being assigned here.
85+
// might be a good idea to flag that default member assignment though...
86+
return false;
87+
}
88+
}
89+
90+
// assign declaration is an object without a default parameterless (or with all parameters optional) member - LHS needs a 'Set' keyword.
3991
return true;
4092
}
4193

42-
//We need to look everything to understand the RHS - the assigned reference is probably a Variant
43-
var allInterestingDeclarations = GetDeclarationsPotentiallyRequiringSetAssignment(state.AllUserDeclarations);
94+
// assigned declaration is a variant. we need to know about the RHS of the assignment.
4495

45-
return ObjectOrVariantRequiresSetAssignment(reference, allInterestingDeclarations);
46-
}
96+
var expression = letStmtContext.expression();
97+
if (expression == null)
98+
{
99+
Debug.Assert(false, "RHS expression is empty? What's going on here?");
100+
}
47101

48-
private static bool MayRequireAssignmentUsingSet(Declaration declaration)
49-
{
50-
if (declaration.DeclarationType == DeclarationType.PropertyLet)
102+
if (expression is VBAParser.NewExprContext)
51103
{
52-
return false;
104+
// RHS expression is newing up an object reference - LHS needs a 'Set' keyword:
105+
return true;
53106
}
54107

108+
var literalExpression = expression as VBAParser.LiteralExprContext;
109+
if (literalExpression?.literalExpression()?.literalIdentifier()?.objectLiteralIdentifier() != null)
110+
{
111+
// RHS is a 'Nothing' token - LHS needs a 'Set' keyword:
112+
return true;
113+
}
114+
115+
// todo resolve expression return type
116+
117+
var memberRefs = state.DeclarationFinder.IdentifierReferences(reference.ParentScoping.QualifiedName);
118+
var lastRef = memberRefs.LastOrDefault(r => !Equals(r, reference) && r.Context.GetAncestor<VBAParser.LetStmtContext>() == letStmtContext);
119+
if (lastRef?.Declaration.AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.ClassModule) ?? false)
120+
{
121+
// the last reference in the expression is referring to an object type
122+
return true;
123+
}
124+
if (lastRef?.Declaration.AsTypeName == Tokens.Object)
125+
{
126+
return true;
127+
}
128+
129+
var accessibleDeclarations = state.DeclarationFinder.GetAccessibleDeclarations(reference.ParentScoping);
130+
foreach (var accessibleDeclaration in accessibleDeclarations.Where(d => d.IdentifierName == expression.GetText()))
131+
{
132+
if (accessibleDeclaration.DeclarationType.HasFlag(DeclarationType.ClassModule) || accessibleDeclaration.AsTypeName == Tokens.Object)
133+
{
134+
return true;
135+
}
136+
}
137+
138+
return false;
139+
}
140+
141+
private static bool MayRequireAssignmentUsingSet(Declaration declaration)
142+
{
55143
if (declaration.AsTypeName == Tokens.Variant)
56144
{
57145
return true;
@@ -82,7 +170,7 @@ private static bool RequiresAssignmentUsingSet(Declaration declaration)
82170
{
83171
if (declaration.AsTypeDeclaration != null)
84172
{
85-
return declaration.AsTypeDeclaration.DeclarationType == DeclarationType.UserDefinedType
173+
return declaration.AsTypeDeclaration.DeclarationType == DeclarationType.ClassModule
86174
&& (((IsVariableOrParameter(declaration)
87175
&& !declaration.IsSelfAssigned)
88176
|| (IsMemberWithReturnType(declaration)
@@ -102,84 +190,5 @@ private static bool IsVariableOrParameter(Declaration item)
102190
return item.DeclarationType == DeclarationType.Variable
103191
|| item.DeclarationType == DeclarationType.Parameter;
104192
}
105-
106-
private static bool ObjectOrVariantRequiresSetAssignment(IdentifierReference objectOrVariantRef, IEnumerable<Declaration> variantAndObjectDeclarations)
107-
{
108-
//Not an assignment...nothing to evaluate
109-
if (!objectOrVariantRef.IsAssignment)
110-
{
111-
return false;
112-
}
113-
114-
if (IsAlreadyAssignedUsingSet(objectOrVariantRef)
115-
|| objectOrVariantRef.Declaration.AsTypeName != Tokens.Variant)
116-
{
117-
return true;
118-
}
119-
120-
//Variants can be assigned with or without 'Set' depending...
121-
var letStmtContext = objectOrVariantRef.Context.GetAncestor<VBAParser.LetStmtContext>();
122-
123-
//A potential error is only possible for let statements: rset, lset and other type specific assignments are always let assignments;
124-
//assignemts in for each loop statements are do not require the set keyword.
125-
if (letStmtContext == null)
126-
{
127-
return false;
128-
}
129-
130-
//You can only new up objects.
131-
if (RHSUsesNew(letStmtContext)) { return true; }
132-
133-
if (RHSIsLiteral(letStmtContext))
134-
{
135-
if(RHSIsObjectLiteral(letStmtContext))
136-
{
137-
return true;
138-
}
139-
//All literals but the object literal potentially do not need a set assignment.
140-
//We cannot get more information from the RHS and do not want false positives.
141-
return false;
142-
}
143-
144-
//If the RHS is the identifierName of one of the 'interesting' declarations, we need to use 'Set'
145-
//unless the 'interesting' declaration is also a Variant
146-
var rhsIdentifier = GetRHSIdentifierExpressionText(letStmtContext);
147-
return variantAndObjectDeclarations.Any(dec => dec.IdentifierName == rhsIdentifier && dec.AsTypeName != Tokens.Variant);
148-
}
149-
150-
private static bool IsLetAssignment(IdentifierReference reference)
151-
{
152-
var letStmtContext = reference.Context.GetAncestor<VBAParser.LetStmtContext>();
153-
return (reference.IsAssignment && letStmtContext != null);
154-
}
155-
156-
private static bool IsAlreadyAssignedUsingSet(IdentifierReference reference)
157-
{
158-
var setStmtContext = reference.Context.GetAncestor<VBAParser.SetStmtContext>();
159-
return (reference.IsAssignment && setStmtContext?.SET() != null);
160-
}
161-
162-
private static string GetRHSIdentifierExpressionText(VBAParser.LetStmtContext letStmtContext)
163-
{
164-
var expression = letStmtContext.expression();
165-
return expression is VBAParser.LExprContext ? expression.GetText() : string.Empty;
166-
}
167-
168-
private static bool RHSUsesNew(VBAParser.LetStmtContext letStmtContext)
169-
{
170-
var expression = letStmtContext.expression();
171-
return (expression is VBAParser.NewExprContext);
172-
}
173-
174-
private static bool RHSIsLiteral(VBAParser.LetStmtContext letStmtContext)
175-
{
176-
return letStmtContext.expression() is VBAParser.LiteralExprContext;
177-
}
178-
179-
private static bool RHSIsObjectLiteral(VBAParser.LetStmtContext letStmtContext)
180-
{
181-
var rhsAsLiteralExpr = letStmtContext.expression() as VBAParser.LiteralExprContext;
182-
return rhsAsLiteralExpr?.literalExpression()?.literalIdentifier()?.objectLiteralIdentifier() != null;
183-
}
184193
}
185194
}

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -339,6 +339,14 @@ private static string CorrectlyFormatedDescription(string literalDescription)
339339
/// </summary>
340340
public bool IsEnumeratorMember => _attributes.Any(a => a.Name.EndsWith("VB_UserMemId") && a.Values.Contains("-4"));
341341

342+
public virtual bool IsObject =>
343+
AsTypeName == Tokens.Object || (
344+
AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.ClassModule) ??
345+
!AsTypeIsBaseType
346+
&& !IsArray
347+
&& !DeclarationType.HasFlag(DeclarationType.UserDefinedType)
348+
&& !DeclarationType.HasFlag(DeclarationType.Enumeration));
349+
342350
public void AddReference(
343351
QualifiedModuleName module,
344352
Declaration scope,

0 commit comments

Comments
 (0)