Skip to content

Commit

Permalink
Merge pull request #2897 from BZngr/next
Browse files Browse the repository at this point in the history
Fixes #2873
  • Loading branch information
retailcoder committed Mar 25, 2017
2 parents 1656ee9 + 5a28e90 commit a1a8ec2
Show file tree
Hide file tree
Showing 9 changed files with 744 additions and 520 deletions.
61 changes: 21 additions & 40 deletions RetailCoder.VBE/Inspections/ObjectVariableNotSetInspection.cs
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 @@ -14,50 +13,32 @@ namespace Rubberduck.Inspections
public sealed class ObjectVariableNotSetInspection : InspectionBase
{
public ObjectVariableNotSetInspection(RubberduckParserState state)
: base(state, CodeInspectionSeverity.Error)
{
}
: base(state, CodeInspectionSeverity.Error) { }

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 =
VariableRequiresSetAssignmentEvaluator.GetDeclarationsPotentiallyRequiringSetAssignment(State.AllUserDeclarations);

var candidateReferencesRequiringSetAssignment =
allInterestingDeclarations.SelectMany(dec => dec.References)
.Where(dec => !IsIgnoringInspectionResultFor(dec, AnnotationName))
.Where(reference => reference.IsAssignment);

var referencesRequiringSetAssignment = candidateReferencesRequiringSetAssignment
.Where(reference => VariableRequiresSetAssignmentEvaluator.RequiresSetAssignment(reference, State));

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);
}
}
}
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 Down Expand Up @@ -99,11 +100,14 @@ private void ReplaceAssignedByValParameterReferences(IModuleRewriter rewriter, s

private void InsertLocalVariableDeclarationAndAssignment(IModuleRewriter rewriter, string localIdentifier)
{
var content = Tokens.Dim + " " + localIdentifier + " " + Tokens.As + " " + _target.AsTypeName + Environment.NewLine
+ (_target.AsTypeDeclaration is ClassModuleDeclaration ? Tokens.Set + " " : string.Empty)
+ localIdentifier + " = " + _target.IdentifierName;
var localVariableDeclaration = $"{Environment.NewLine}{Tokens.Dim} {localIdentifier} {Tokens.As} {_target.AsTypeName}{Environment.NewLine}";

var requiresAssignmentUsingSet =
_target.References.Any(refItem => VariableRequiresSetAssignmentEvaluator.RequiresSetAssignment(refItem, _parserState));

rewriter.InsertBefore(((ParserRuleContext)_target.Context.Parent).Stop.TokenIndex + 1, "\r\n" + content);
var localVariableAssignment = requiresAssignmentUsingSet ? $"Set {localIdentifier} = {_target.IdentifierName}" : $"{localIdentifier} = {_target.IdentifierName}";

rewriter.InsertBefore(((ParserRuleContext)_target.Context.Parent).Stop.TokenIndex + 1, localVariableDeclaration + localVariableAssignment);
}
}
}
151 changes: 151 additions & 0 deletions RetailCoder.VBE/Inspections/VariableRequiresSetAssignmentEvaluator.cs
@@ -0,0 +1,151 @@
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
{
public static class VariableRequiresSetAssignmentEvaluator
{
public static IEnumerable<Declaration> GetDeclarationsPotentiallyRequiringSetAssignment(IEnumerable<Declaration> declarations)
{
//Reduce most of the declaration list with the easy ones
var relevantDeclarations = declarations.Where(dec => dec.AsTypeName == Tokens.Variant
|| !SymbolList.ValueTypes.Contains(dec.AsTypeName)
&&(MayRequireAssignmentUsingSet(dec) || RequiresAssignmentUsingSet(dec)));

return relevantDeclarations;
}

public static bool RequiresSetAssignment(IdentifierReference reference, RubberduckParserState state)
{
//Not an assignment...definitely does not require a 'Set' assignment
if (!reference.IsAssignment) { return false; }

//We know for sure it DOES NOT use 'Set'
if (!MayRequireAssignmentUsingSet(reference.Declaration)) { return false; }

//We know for sure that it DOES use 'Set'
if (RequiresAssignmentUsingSet(reference.Declaration)) { return true; }

//We need to look everything to understand the RHS - the assigned reference is probably a Variant
var allInterestingDeclarations = GetDeclarationsPotentiallyRequiringSetAssignment(state.AllUserDeclarations);

return ObjectOrVariantRequiresSetAssignment(reference, allInterestingDeclarations);
}

private static bool MayRequireAssignmentUsingSet(Declaration declaration)
{
if (declaration.AsTypeName == Tokens.Variant) { return true; }

if (declaration.IsArray) { return false; }

if (declaration.AsTypeDeclaration != null)
{
if ((ClassModuleDeclaration.HasDefaultMember(declaration.AsTypeDeclaration)
|| declaration.AsTypeDeclaration.DeclarationType == DeclarationType.Enumeration))
{
return false;
}
}

if (SymbolList.ValueTypes.Contains(declaration.AsTypeName))
{
return false;
}
return true;
}

private static bool RequiresAssignmentUsingSet(Declaration declaration)
{
if (declaration.AsTypeDeclaration != null)
{
return declaration.AsTypeDeclaration.DeclarationType == DeclarationType.UserDefinedType
&& (((IsVariableOrParameter(declaration) && !declaration.IsSelfAssigned)
|| (IsMemberWithReturnType(declaration) && declaration.IsTypeSpecified)));
}
return false;
}

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

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

private static bool ObjectOrVariantRequiresSetAssignment(IdentifierReference objectOrVariantRef, IEnumerable<Declaration> variantAndObjectDeclarations)
{
//Not an assignment...nothing to evaluate
if (!objectOrVariantRef.IsAssignment)
{
return false;
}

if (IsAlreadyAssignedUsingSet(objectOrVariantRef)
|| objectOrVariantRef.Declaration.AsTypeName != Tokens.Variant)
{
return true;
}

//Variants can be assigned with or without 'Set' depending...
var letStmtContext = ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(objectOrVariantRef.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 static bool IsLetAssignment(IdentifierReference reference)
{
var letStmtContext = ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(reference.Context);
return (reference.IsAssignment && letStmtContext != null);
}

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

private static 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 static 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
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

0 comments on commit a1a8ec2

Please sign in to comment.