Skip to content

Commit

Permalink
Enhanced detection of variable 'Set' requirement
Browse files Browse the repository at this point in the history
  • Loading branch information
BZngr committed Mar 21, 2017
1 parent b46210c commit 811df21
Show file tree
Hide file tree
Showing 6 changed files with 335 additions and 134 deletions.
58 changes: 21 additions & 37 deletions RetailCoder.VBE/Inspections/ObjectVariableNotSetInspection.cs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@
using System.Linq;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.Inspections.Resources;
Expand All @@ -13,51 +12,36 @@ namespace Rubberduck.Inspections
{
public sealed class ObjectVariableNotSetInspection : InspectionBase
{
private readonly VariableRequiresSetAssignmentEvaluator _setRequirementEvaluator;

public ObjectVariableNotSetInspection(RubberduckParserState state)
: base(state, CodeInspectionSeverity.Error)
{
_setRequirementEvaluator = new VariableRequiresSetAssignmentEvaluator(state);
}

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

public override IEnumerable<IInspectionResult> GetInspectionResults()
{
var interestingDeclarations =
State.AllUserDeclarations.Where(item =>
!item.IsSelfAssigned &&
!item.IsArray &&
!SymbolList.ValueTypes.Contains(item.AsTypeName) &&
(item.AsTypeDeclaration == null || (!ClassModuleDeclaration.HasDefaultMember(item.AsTypeDeclaration) &&
item.AsTypeDeclaration.DeclarationType != DeclarationType.Enumeration &&
item.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType)) &&
(item.DeclarationType == DeclarationType.Variable ||
item.DeclarationType == DeclarationType.Parameter));

var interestingMembers =
State.AllUserDeclarations.Where(item =>
(item.DeclarationType == DeclarationType.Function || item.DeclarationType == DeclarationType.PropertyGet)
&& !item.IsArray
&& item.IsTypeSpecified
&& !SymbolList.ValueTypes.Contains(item.AsTypeName)
&& (item.AsTypeDeclaration == null // null if unresolved (e.g. in unit tests)
|| (item.AsTypeDeclaration.DeclarationType != DeclarationType.Enumeration && item.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType
&& item.AsTypeDeclaration != null
&& !ClassModuleDeclaration.HasDefaultMember(item.AsTypeDeclaration))));

var interestingReferences = interestingDeclarations
.Union(interestingMembers.SelectMany(item =>
item.References.Where(reference => reference.ParentScoping.Equals(item) && reference.IsAssignment)
.Select(reference => reference.Declaration)))
.SelectMany(declaration =>
declaration.References.Where(reference =>
{
var letStmtContext = ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(reference.Context);
return reference.IsAssignment && letStmtContext != null && letStmtContext.LET() == null;
})
);


return interestingReferences.Select(reference => new ObjectVariableNotSetInspectionResult(this, reference));
var allInterestingDeclarations =
_setRequirementEvaluator.GetDeclarationsPotentiallyRequiringSetAssignment();

var candidateReferencesRequiringSetAssignment =
allInterestingDeclarations.SelectMany(dec => dec.References);

var referencesRequiringSetAssignment = candidateReferencesRequiringSetAssignment
.Where(reference => _setRequirementEvaluator.RequiresSetAssignment(reference));

var objectVariableNotSetReferences = referencesRequiringSetAssignment.Where(reference => FlagIfObjectVariableNotSet(reference));

return objectVariableNotSetReferences.Select(reference => new ObjectVariableNotSetInspectionResult(this, reference));
}

private bool FlagIfObjectVariableNotSet(IdentifierReference reference)
{
var letStmtContext = ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(reference.Context);
return (reference.IsAssignment && letStmtContext != null && letStmtContext.LET() == null);
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@
using Rubberduck.Parsing.Inspections.Resources;
using Rubberduck.Parsing.PostProcessing;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing;

namespace Rubberduck.Inspections.QuickFixes
{
Expand All @@ -21,6 +22,7 @@ public class AssignedByValParameterMakeLocalCopyQuickFix : QuickFixBase
private readonly IAssignedByValParameterQuickFixDialogFactory _dialogFactory;
private readonly RubberduckParserState _parserState;
private readonly IEnumerable<string> _forbiddenNames;
private readonly VariableRequiresSetAssignmentEvaluator _setRequirementEvaluator;

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

public override bool CanFixInModule => false;
Expand Down Expand Up @@ -97,42 +100,25 @@ private void ReplaceAssignedByValParameterReferences(IModuleRewriter rewriter, s
}
}


private void InsertLocalVariableDeclarationAndAssignment(IModuleRewriter rewriter, string localIdentifier)
{
var content = Tokens.Dim + " " + localIdentifier + " " + Tokens.As + " " + _target.AsTypeName + Environment.NewLine;
if (IsBaseTypeContext(_target))
{
content = content + localIdentifier + " = " + _target.IdentifierName;
}
else
string assignmentFormat = "{0} = {1}";
if (RequiresSetAssignment(_target))
{
//All we can know is that it is not a Base type. Let VBA determine
//the right way to assign the parameter. The user can simplify it later.
string insertIsObjectCheck =
@"If(IsObject({1})) Then
Set {0} = {1}
Else
{0} = {1}
End If";
content = content
+ string.Format(insertIsObjectCheck, localIdentifier, _target.IdentifierName);
assignmentFormat = "Set {0} = {1}";
}

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

private bool IsBaseTypeContext(Declaration target)
private bool RequiresSetAssignment(Declaration declaration)
{
var argContext = target.Context as VBAParser.ArgContext;
var asTypeClause = argContext.asTypeClause();
if (null == asTypeClause)
{
return false;
}
var typeCtxt = asTypeClause.type().baseType();
var requiresAssignmentUsingSet =
declaration.References.Where(refItem => _setRequirementEvaluator.RequiresSetAssignment(refItem)).Any();

return (typeCtxt is VBAParser.BaseTypeContext);
return requiresAssignmentUsingSet;
}
}
}
160 changes: 160 additions & 0 deletions RetailCoder.VBE/Inspections/VariableRequiresSetAssignmentEvaluator.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,160 @@
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using System.Collections.Generic;
using System.Linq;

namespace Rubberduck.Inspections
{
class VariableRequiresSetAssignmentEvaluator
{
private readonly RubberduckParserState _parserState;
public VariableRequiresSetAssignmentEvaluator(RubberduckParserState parserState)
{
_parserState = parserState;
}

public IEnumerable<Declaration> GetDeclarationsPotentiallyRequiringSetAssignment()
{
var interestingDeclarations = _parserState.AllUserDeclarations.Where(item =>
IsVariableOrParameter(item)
&& !item.IsSelfAssigned
&& TypeIsAnObjectOrVariant(item));

var interestingMembers = _parserState.AllUserDeclarations.Where(item =>
IsMemberWithReturnType(item)
&& item.IsTypeSpecified
&& TypeIsAnObjectOrVariant(item));

var allInterestingDeclarations = interestingDeclarations
.Union(HasReturnAssignment(interestingMembers));

return allInterestingDeclarations;
}

public bool RequiresSetAssignment(IdentifierReference reference)
{
var declaration = reference.Declaration;
var MayRequireAssignmentUsingSet =
(IsVariableOrParameter(declaration) || IsMemberWithReturnType(declaration) )
&& !declaration.IsSelfAssigned
&& TypeIsAnObjectOrVariant(declaration);

if(!MayRequireAssignmentUsingSet) { return false; }

var allInterestingDeclarations = GetDeclarationsPotentiallyRequiringSetAssignment();

return ObjectOrVariantRequiresSetAssignment(reference, allInterestingDeclarations);
}

private bool IsMemberWithReturnType(Declaration item)
{
return (item.DeclarationType == DeclarationType.Function
|| item.DeclarationType == DeclarationType.PropertyGet);
}

private IEnumerable<Declaration> HasReturnAssignment(IEnumerable<Declaration> interestingMembers)
{
return interestingMembers.SelectMany(member =>
member.References.Where(memberRef => memberRef.ParentScoping.Equals(member)
&& memberRef.IsAssignment)).Select(reference => reference.Declaration);
}

private bool IsVariableOrParameter(Declaration item)
{
return item.DeclarationType == DeclarationType.Variable
|| item.DeclarationType == DeclarationType.Parameter;
}

private bool TypeIsAnObjectOrVariant(Declaration item)
{
return !item.IsArray
&& !ValueOnlyTypes().Contains(item.AsTypeName)
&& (item.AsTypeDeclaration == null
|| TypeRequiresSetAssignment(item));
}

private IEnumerable<string> ValueOnlyTypes()
{
var nonSetTypes = SymbolList.ValueTypes.ToList();
nonSetTypes.Remove(Tokens.Variant);
return nonSetTypes;
}

private bool TypeRequiresSetAssignment(Declaration item)
{
return (!ClassModuleDeclaration.HasDefaultMember(item.AsTypeDeclaration))
&& (item.AsTypeDeclaration.DeclarationType != DeclarationType.Enumeration
&& item.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType
&& item.AsTypeDeclaration != null);
}

private bool ObjectOrVariantRequiresSetAssignment(IdentifierReference variantOrObjectRef, IEnumerable<Declaration> variantAndObjectDeclarations)
{
//Not an assignment...not interested
if (!variantOrObjectRef.IsAssignment)
{
return false;
}

//Already assigned using 'Set'
if (IsSetAssignment(variantOrObjectRef)) { return true; };

if (variantOrObjectRef.Declaration.AsTypeName != Tokens.Variant) { return true; }

//Variants can be assigned with or without 'Set' depending...
var letStmtContext = ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(variantOrObjectRef.Context);

//definitely needs to use "Set". e.g., 'Variant myVar = new Collection'
if (RHSUsesNew(letStmtContext)) { return true; }

//If the RHS is the identifierName of one of the 'interesting' declarations, we need to use 'Set'
//unless the 'interesting' declaration is also a Variant
var rhsIdentifier = GetRHSIdentifier(letStmtContext);
return variantAndObjectDeclarations
.Where(dec => dec.IdentifierName == rhsIdentifier && dec.AsTypeName != Tokens.Variant).Any();
}


private bool IsLetAssignment(IdentifierReference reference)
{
var letStmtContext = ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(reference.Context);
return (reference.IsAssignment && letStmtContext != null);
}

private bool IsSetAssignment(IdentifierReference reference)
{
var setStmtContext = ParserRuleContextHelper.GetParent<VBAParser.SetStmtContext>(reference.Context);
return (reference.IsAssignment && setStmtContext != null && setStmtContext.SET() != null);
}

private string GetRHSIdentifier(VBAParser.LetStmtContext letStmtContext)
{
for (var idx = 0; idx < letStmtContext.ChildCount; idx++)
{
var child = letStmtContext.GetChild(idx);
if ((child is VBAParser.LiteralExprContext)
|| (child is VBAParser.LExprContext))
{
return child.GetText();
}
}
return string.Empty;
}

private bool RHSUsesNew(VBAParser.LetStmtContext letStmtContext)
{
for (var idx = 0; idx < letStmtContext.ChildCount; idx++)
{
var child = letStmtContext.GetChild(idx);
if ((child is VBAParser.NewExprContext)
|| (child is VBAParser.CtNewExprContext))
{
return true;
}
}
return false;
}
}
}
1 change: 1 addition & 0 deletions RetailCoder.VBE/Rubberduck.csproj
Original file line number Diff line number Diff line change
Expand Up @@ -406,6 +406,7 @@
<Compile Include="Inspections\QuickFixes\WriteOnlyPropertyQuickFix.cs" />
<Compile Include="Inspections\Results\WriteOnlyPropertyInspectionResult.cs" />
<Compile Include="Inspections\VariableNameValidator.cs" />
<Compile Include="Inspections\VariableRequiresSetAssignmentEvaluator.cs" />
<Compile Include="Navigation\CodeExplorer\ICodeExplorerDeclarationViewModel.cs" />
<Compile Include="Navigation\Folders\FolderHelper.cs" />
<Compile Include="Refactorings\EncapsulateField\PropertyGenerator.cs" />
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -185,11 +185,7 @@ public void AssignedByValParameter_LocalVariableAssignment_UsesSet()
@"
Public Sub Foo(FirstArg As Long, ByVal arg1 As Range)
Dim localArg1 As Range
If(IsObject(arg1)) Then
Set localArg1 = arg1
Else
localArg1 = arg1
End If
Set localArg1 = arg1
localArg1 = Range(""A1: C4"")
End Sub"
;
Expand All @@ -213,11 +209,7 @@ public void AssignedByValParameter_LocalVariableAssignment_NoAsTypeClause()
@"
Public Sub Foo(FirstArg As Long, ByVal arg1)
Dim localArg1 As Variant
If(IsObject(arg1)) Then
Set localArg1 = arg1
Else
localArg1 = arg1
End If
localArg1 = arg1
localArg1 = Range(""A1: C4"")
End Sub"
;
Expand All @@ -232,21 +224,29 @@ public void AssignedByValParameter_LocalVariableAssignment_EnumType()
{
var inputCode =
@"
Public Sub Foo(FirstArg As Long, ByVal arg1 As VBA.vbMessageBoxResult)
arg1 = vbIgnore
Enum TestEnum
EnumOne
EnumTwo
EnumThree
End Enum
Public Sub Foo(FirstArg As Long, ByVal arg1 As TestEnum)
arg1 = EnumThree
End Sub"
;

var expectedCode =
@"
Public Sub Foo(FirstArg As Long, ByVal arg1 As VBA.vbMessageBoxResult)
Dim localArg1 As VBA.vbMessageBoxResult
If(IsObject(arg1)) Then
Set localArg1 = arg1
Else
localArg1 = arg1
End If
localArg1 = vbIgnore
Enum TestEnum
EnumOne
EnumTwo
EnumThree
End Enum
Public Sub Foo(FirstArg As Long, ByVal arg1 As TestEnum)
Dim localArg1 As TestEnum
localArg1 = arg1
localArg1 = EnumThree
End Sub"
;
var quickFixResult = ApplyLocalVariableQuickFixToCodeFragment(inputCode);
Expand Down

0 comments on commit 811df21

Please sign in to comment.