Skip to content

Commit 811df21

Browse files
committed
Enhanced detection of variable 'Set' requirement
1 parent b46210c commit 811df21

File tree

6 files changed

+335
-134
lines changed

6 files changed

+335
-134
lines changed

RetailCoder.VBE/Inspections/ObjectVariableNotSetInspection.cs

Lines changed: 21 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
using System.Linq;
33
using Rubberduck.Inspections.Abstract;
44
using Rubberduck.Inspections.Results;
5-
using Rubberduck.Parsing;
65
using Rubberduck.Parsing.Grammar;
76
using Rubberduck.Parsing.Inspections.Abstract;
87
using Rubberduck.Parsing.Inspections.Resources;
@@ -13,51 +12,36 @@ namespace Rubberduck.Inspections
1312
{
1413
public sealed class ObjectVariableNotSetInspection : InspectionBase
1514
{
15+
private readonly VariableRequiresSetAssignmentEvaluator _setRequirementEvaluator;
16+
1617
public ObjectVariableNotSetInspection(RubberduckParserState state)
1718
: base(state, CodeInspectionSeverity.Error)
1819
{
20+
_setRequirementEvaluator = new VariableRequiresSetAssignmentEvaluator(state);
1921
}
2022

2123
public override CodeInspectionType InspectionType { get { return CodeInspectionType.CodeQualityIssues; } }
2224

2325
public override IEnumerable<IInspectionResult> GetInspectionResults()
2426
{
25-
var interestingDeclarations =
26-
State.AllUserDeclarations.Where(item =>
27-
!item.IsSelfAssigned &&
28-
!item.IsArray &&
29-
!SymbolList.ValueTypes.Contains(item.AsTypeName) &&
30-
(item.AsTypeDeclaration == null || (!ClassModuleDeclaration.HasDefaultMember(item.AsTypeDeclaration) &&
31-
item.AsTypeDeclaration.DeclarationType != DeclarationType.Enumeration &&
32-
item.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType)) &&
33-
(item.DeclarationType == DeclarationType.Variable ||
34-
item.DeclarationType == DeclarationType.Parameter));
35-
36-
var interestingMembers =
37-
State.AllUserDeclarations.Where(item =>
38-
(item.DeclarationType == DeclarationType.Function || item.DeclarationType == DeclarationType.PropertyGet)
39-
&& !item.IsArray
40-
&& item.IsTypeSpecified
41-
&& !SymbolList.ValueTypes.Contains(item.AsTypeName)
42-
&& (item.AsTypeDeclaration == null // null if unresolved (e.g. in unit tests)
43-
|| (item.AsTypeDeclaration.DeclarationType != DeclarationType.Enumeration && item.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType
44-
&& item.AsTypeDeclaration != null
45-
&& !ClassModuleDeclaration.HasDefaultMember(item.AsTypeDeclaration))));
46-
47-
var interestingReferences = interestingDeclarations
48-
.Union(interestingMembers.SelectMany(item =>
49-
item.References.Where(reference => reference.ParentScoping.Equals(item) && reference.IsAssignment)
50-
.Select(reference => reference.Declaration)))
51-
.SelectMany(declaration =>
52-
declaration.References.Where(reference =>
53-
{
54-
var letStmtContext = ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(reference.Context);
55-
return reference.IsAssignment && letStmtContext != null && letStmtContext.LET() == null;
56-
})
57-
);
58-
59-
60-
return interestingReferences.Select(reference => new ObjectVariableNotSetInspectionResult(this, reference));
27+
var allInterestingDeclarations =
28+
_setRequirementEvaluator.GetDeclarationsPotentiallyRequiringSetAssignment();
29+
30+
var candidateReferencesRequiringSetAssignment =
31+
allInterestingDeclarations.SelectMany(dec => dec.References);
32+
33+
var referencesRequiringSetAssignment = candidateReferencesRequiringSetAssignment
34+
.Where(reference => _setRequirementEvaluator.RequiresSetAssignment(reference));
35+
36+
var objectVariableNotSetReferences = referencesRequiringSetAssignment.Where(reference => FlagIfObjectVariableNotSet(reference));
37+
38+
return objectVariableNotSetReferences.Select(reference => new ObjectVariableNotSetInspectionResult(this, reference));
39+
}
40+
41+
private bool FlagIfObjectVariableNotSet(IdentifierReference reference)
42+
{
43+
var letStmtContext = ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(reference.Context);
44+
return (reference.IsAssignment && letStmtContext != null && letStmtContext.LET() == null);
6145
}
6246
}
6347
}

RetailCoder.VBE/Inspections/QuickFixes/AssignedByValParameterMakeLocalCopyQuickFix.cs

Lines changed: 11 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@
1212
using Rubberduck.Parsing.Inspections.Resources;
1313
using Rubberduck.Parsing.PostProcessing;
1414
using Rubberduck.Parsing.VBA;
15+
using Rubberduck.Parsing;
1516

1617
namespace Rubberduck.Inspections.QuickFixes
1718
{
@@ -21,6 +22,7 @@ public class AssignedByValParameterMakeLocalCopyQuickFix : QuickFixBase
2122
private readonly IAssignedByValParameterQuickFixDialogFactory _dialogFactory;
2223
private readonly RubberduckParserState _parserState;
2324
private readonly IEnumerable<string> _forbiddenNames;
25+
private readonly VariableRequiresSetAssignmentEvaluator _setRequirementEvaluator;
2426

2527
public AssignedByValParameterMakeLocalCopyQuickFix(Declaration target, QualifiedSelection selection, RubberduckParserState parserState, IAssignedByValParameterQuickFixDialogFactory dialogFactory)
2628
: base(target.Context, selection, InspectionsUI.AssignedByValParameterMakeLocalCopyQuickFix)
@@ -29,6 +31,7 @@ public AssignedByValParameterMakeLocalCopyQuickFix(Declaration target, Qualified
2931
_dialogFactory = dialogFactory;
3032
_parserState = parserState;
3133
_forbiddenNames = parserState.DeclarationFinder.GetDeclarationsWithIdentifiersToAvoid(target).Select(n => n.IdentifierName);
34+
_setRequirementEvaluator = new VariableRequiresSetAssignmentEvaluator(_parserState);
3235
}
3336

3437
public override bool CanFixInModule => false;
@@ -97,42 +100,25 @@ private void ReplaceAssignedByValParameterReferences(IModuleRewriter rewriter, s
97100
}
98101
}
99102

100-
101103
private void InsertLocalVariableDeclarationAndAssignment(IModuleRewriter rewriter, string localIdentifier)
102104
{
103105
var content = Tokens.Dim + " " + localIdentifier + " " + Tokens.As + " " + _target.AsTypeName + Environment.NewLine;
104-
if (IsBaseTypeContext(_target))
105-
{
106-
content = content + localIdentifier + " = " + _target.IdentifierName;
107-
}
108-
else
106+
string assignmentFormat = "{0} = {1}";
107+
if (RequiresSetAssignment(_target))
109108
{
110-
//All we can know is that it is not a Base type. Let VBA determine
111-
//the right way to assign the parameter. The user can simplify it later.
112-
string insertIsObjectCheck =
113-
@"If(IsObject({1})) Then
114-
Set {0} = {1}
115-
Else
116-
{0} = {1}
117-
End If";
118-
content = content
119-
+ string.Format(insertIsObjectCheck, localIdentifier, _target.IdentifierName);
109+
assignmentFormat = "Set {0} = {1}";
120110
}
121111

112+
content = content + string.Format(assignmentFormat, localIdentifier, _target.IdentifierName);
122113
rewriter.InsertBefore(((ParserRuleContext)_target.Context.Parent).Stop.TokenIndex + 1, "\r\n" + content);
123114
}
124115

125-
private bool IsBaseTypeContext(Declaration target)
116+
private bool RequiresSetAssignment(Declaration declaration)
126117
{
127-
var argContext = target.Context as VBAParser.ArgContext;
128-
var asTypeClause = argContext.asTypeClause();
129-
if (null == asTypeClause)
130-
{
131-
return false;
132-
}
133-
var typeCtxt = asTypeClause.type().baseType();
118+
var requiresAssignmentUsingSet =
119+
declaration.References.Where(refItem => _setRequirementEvaluator.RequiresSetAssignment(refItem)).Any();
134120

135-
return (typeCtxt is VBAParser.BaseTypeContext);
121+
return requiresAssignmentUsingSet;
136122
}
137123
}
138124
}
Lines changed: 160 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,160 @@
1+
using Rubberduck.Parsing;
2+
using Rubberduck.Parsing.Grammar;
3+
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Parsing.VBA;
5+
using System.Collections.Generic;
6+
using System.Linq;
7+
8+
namespace Rubberduck.Inspections
9+
{
10+
class VariableRequiresSetAssignmentEvaluator
11+
{
12+
private readonly RubberduckParserState _parserState;
13+
public VariableRequiresSetAssignmentEvaluator(RubberduckParserState parserState)
14+
{
15+
_parserState = parserState;
16+
}
17+
18+
public IEnumerable<Declaration> GetDeclarationsPotentiallyRequiringSetAssignment()
19+
{
20+
var interestingDeclarations = _parserState.AllUserDeclarations.Where(item =>
21+
IsVariableOrParameter(item)
22+
&& !item.IsSelfAssigned
23+
&& TypeIsAnObjectOrVariant(item));
24+
25+
var interestingMembers = _parserState.AllUserDeclarations.Where(item =>
26+
IsMemberWithReturnType(item)
27+
&& item.IsTypeSpecified
28+
&& TypeIsAnObjectOrVariant(item));
29+
30+
var allInterestingDeclarations = interestingDeclarations
31+
.Union(HasReturnAssignment(interestingMembers));
32+
33+
return allInterestingDeclarations;
34+
}
35+
36+
public bool RequiresSetAssignment(IdentifierReference reference)
37+
{
38+
var declaration = reference.Declaration;
39+
var MayRequireAssignmentUsingSet =
40+
(IsVariableOrParameter(declaration) || IsMemberWithReturnType(declaration) )
41+
&& !declaration.IsSelfAssigned
42+
&& TypeIsAnObjectOrVariant(declaration);
43+
44+
if(!MayRequireAssignmentUsingSet) { return false; }
45+
46+
var allInterestingDeclarations = GetDeclarationsPotentiallyRequiringSetAssignment();
47+
48+
return ObjectOrVariantRequiresSetAssignment(reference, allInterestingDeclarations);
49+
}
50+
51+
private bool IsMemberWithReturnType(Declaration item)
52+
{
53+
return (item.DeclarationType == DeclarationType.Function
54+
|| item.DeclarationType == DeclarationType.PropertyGet);
55+
}
56+
57+
private IEnumerable<Declaration> HasReturnAssignment(IEnumerable<Declaration> interestingMembers)
58+
{
59+
return interestingMembers.SelectMany(member =>
60+
member.References.Where(memberRef => memberRef.ParentScoping.Equals(member)
61+
&& memberRef.IsAssignment)).Select(reference => reference.Declaration);
62+
}
63+
64+
private bool IsVariableOrParameter(Declaration item)
65+
{
66+
return item.DeclarationType == DeclarationType.Variable
67+
|| item.DeclarationType == DeclarationType.Parameter;
68+
}
69+
70+
private bool TypeIsAnObjectOrVariant(Declaration item)
71+
{
72+
return !item.IsArray
73+
&& !ValueOnlyTypes().Contains(item.AsTypeName)
74+
&& (item.AsTypeDeclaration == null
75+
|| TypeRequiresSetAssignment(item));
76+
}
77+
78+
private IEnumerable<string> ValueOnlyTypes()
79+
{
80+
var nonSetTypes = SymbolList.ValueTypes.ToList();
81+
nonSetTypes.Remove(Tokens.Variant);
82+
return nonSetTypes;
83+
}
84+
85+
private bool TypeRequiresSetAssignment(Declaration item)
86+
{
87+
return (!ClassModuleDeclaration.HasDefaultMember(item.AsTypeDeclaration))
88+
&& (item.AsTypeDeclaration.DeclarationType != DeclarationType.Enumeration
89+
&& item.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType
90+
&& item.AsTypeDeclaration != null);
91+
}
92+
93+
private bool ObjectOrVariantRequiresSetAssignment(IdentifierReference variantOrObjectRef, IEnumerable<Declaration> variantAndObjectDeclarations)
94+
{
95+
//Not an assignment...not interested
96+
if (!variantOrObjectRef.IsAssignment)
97+
{
98+
return false;
99+
}
100+
101+
//Already assigned using 'Set'
102+
if (IsSetAssignment(variantOrObjectRef)) { return true; };
103+
104+
if (variantOrObjectRef.Declaration.AsTypeName != Tokens.Variant) { return true; }
105+
106+
//Variants can be assigned with or without 'Set' depending...
107+
var letStmtContext = ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(variantOrObjectRef.Context);
108+
109+
//definitely needs to use "Set". e.g., 'Variant myVar = new Collection'
110+
if (RHSUsesNew(letStmtContext)) { return true; }
111+
112+
//If the RHS is the identifierName of one of the 'interesting' declarations, we need to use 'Set'
113+
//unless the 'interesting' declaration is also a Variant
114+
var rhsIdentifier = GetRHSIdentifier(letStmtContext);
115+
return variantAndObjectDeclarations
116+
.Where(dec => dec.IdentifierName == rhsIdentifier && dec.AsTypeName != Tokens.Variant).Any();
117+
}
118+
119+
120+
private bool IsLetAssignment(IdentifierReference reference)
121+
{
122+
var letStmtContext = ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(reference.Context);
123+
return (reference.IsAssignment && letStmtContext != null);
124+
}
125+
126+
private bool IsSetAssignment(IdentifierReference reference)
127+
{
128+
var setStmtContext = ParserRuleContextHelper.GetParent<VBAParser.SetStmtContext>(reference.Context);
129+
return (reference.IsAssignment && setStmtContext != null && setStmtContext.SET() != null);
130+
}
131+
132+
private string GetRHSIdentifier(VBAParser.LetStmtContext letStmtContext)
133+
{
134+
for (var idx = 0; idx < letStmtContext.ChildCount; idx++)
135+
{
136+
var child = letStmtContext.GetChild(idx);
137+
if ((child is VBAParser.LiteralExprContext)
138+
|| (child is VBAParser.LExprContext))
139+
{
140+
return child.GetText();
141+
}
142+
}
143+
return string.Empty;
144+
}
145+
146+
private bool RHSUsesNew(VBAParser.LetStmtContext letStmtContext)
147+
{
148+
for (var idx = 0; idx < letStmtContext.ChildCount; idx++)
149+
{
150+
var child = letStmtContext.GetChild(idx);
151+
if ((child is VBAParser.NewExprContext)
152+
|| (child is VBAParser.CtNewExprContext))
153+
{
154+
return true;
155+
}
156+
}
157+
return false;
158+
}
159+
}
160+
}

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -406,6 +406,7 @@
406406
<Compile Include="Inspections\QuickFixes\WriteOnlyPropertyQuickFix.cs" />
407407
<Compile Include="Inspections\Results\WriteOnlyPropertyInspectionResult.cs" />
408408
<Compile Include="Inspections\VariableNameValidator.cs" />
409+
<Compile Include="Inspections\VariableRequiresSetAssignmentEvaluator.cs" />
409410
<Compile Include="Navigation\CodeExplorer\ICodeExplorerDeclarationViewModel.cs" />
410411
<Compile Include="Navigation\Folders\FolderHelper.cs" />
411412
<Compile Include="Refactorings\EncapsulateField\PropertyGenerator.cs" />

RubberduckTests/Inspections/AssignedByValParameterMakeLocalCopyQuickFixTests.cs

Lines changed: 20 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -185,11 +185,7 @@ End Sub"
185185
@"
186186
Public Sub Foo(FirstArg As Long, ByVal arg1 As Range)
187187
Dim localArg1 As Range
188-
If(IsObject(arg1)) Then
189-
Set localArg1 = arg1
190-
Else
191-
localArg1 = arg1
192-
End If
188+
Set localArg1 = arg1
193189
localArg1 = Range(""A1: C4"")
194190
End Sub"
195191
;
@@ -213,11 +209,7 @@ End Sub"
213209
@"
214210
Public Sub Foo(FirstArg As Long, ByVal arg1)
215211
Dim localArg1 As Variant
216-
If(IsObject(arg1)) Then
217-
Set localArg1 = arg1
218-
Else
219-
localArg1 = arg1
220-
End If
212+
localArg1 = arg1
221213
localArg1 = Range(""A1: C4"")
222214
End Sub"
223215
;
@@ -232,21 +224,29 @@ public void AssignedByValParameter_LocalVariableAssignment_EnumType()
232224
{
233225
var inputCode =
234226
@"
235-
Public Sub Foo(FirstArg As Long, ByVal arg1 As VBA.vbMessageBoxResult)
236-
arg1 = vbIgnore
227+
Enum TestEnum
228+
EnumOne
229+
EnumTwo
230+
EnumThree
231+
End Enum
232+
233+
Public Sub Foo(FirstArg As Long, ByVal arg1 As TestEnum)
234+
arg1 = EnumThree
237235
End Sub"
238236
;
239237

240238
var expectedCode =
241239
@"
242-
Public Sub Foo(FirstArg As Long, ByVal arg1 As VBA.vbMessageBoxResult)
243-
Dim localArg1 As VBA.vbMessageBoxResult
244-
If(IsObject(arg1)) Then
245-
Set localArg1 = arg1
246-
Else
247-
localArg1 = arg1
248-
End If
249-
localArg1 = vbIgnore
240+
Enum TestEnum
241+
EnumOne
242+
EnumTwo
243+
EnumThree
244+
End Enum
245+
246+
Public Sub Foo(FirstArg As Long, ByVal arg1 As TestEnum)
247+
Dim localArg1 As TestEnum
248+
localArg1 = arg1
249+
localArg1 = EnumThree
250250
End Sub"
251251
;
252252
var quickFixResult = ApplyLocalVariableQuickFixToCodeFragment(inputCode);

0 commit comments

Comments
 (0)