Skip to content

Commit

Permalink
Merge remote-tracking branch 'upstream/next' into Issue5109_Consolida…
Browse files Browse the repository at this point in the history
…te_copy_command_logic
  • Loading branch information
IvenBach committed Aug 28, 2019
2 parents 4666115 + 80948b8 commit 9227d59
Show file tree
Hide file tree
Showing 75 changed files with 3,954 additions and 3,163 deletions.
1 change: 1 addition & 0 deletions .gitignore
Expand Up @@ -189,3 +189,4 @@ Rubberduck.CodeAnalysis.xml

#Gradle
/.gradle/
/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.xml
Expand Up @@ -48,43 +48,12 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
.Cast<ParameterDeclaration>()
.Where(item => !item.IsByRef
&& !item.IsIgnoringInspectionResultFor(AnnotationName)
&& item.References.Any(IsAssignmentToDeclaration));
&& item.References.Any(reference => reference.IsAssignment));

return parameters
.Select(param => new DeclarationInspectionResult(this,
string.Format(InspectionResults.AssignedByValParameterInspection, param.IdentifierName),
param));
}

private static bool IsAssignmentToDeclaration(IdentifierReference reference)
{
//Todo: Review whether this is still needed once parameterless default member assignments are resolved correctly.

if (!reference.IsAssignment)
{
return false;
}

if (reference.IsSetAssignment)
{
return true;
}

var declaration = reference.Declaration;
if (declaration == null)
{
return false;
}

if (declaration.IsObject)
{
//This can only be legal with a default member access.
return false;
}

//This is not perfect in case the referenced declaration is an unbound Variant.
//In that case, a default member access might occur after the run-time resolution.
return true;
}
}
}
@@ -1,10 +1,7 @@
using System.Collections.Generic;
using System.Diagnostics;
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.Resources.Inspections;
using Rubberduck.Parsing.Symbols;
Expand Down Expand Up @@ -40,28 +37,42 @@ public ImplicitDefaultMemberAssignmentInspection(RubberduckParserState state)

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var interestingDeclarations =
State.AllDeclarations.Where(item =>
item.AsTypeDeclaration != null
&& ClassModuleDeclaration.HasDefaultMember(item.AsTypeDeclaration));
var boundDefaultMemberAssignments = State.DeclarationFinder
.AllIdentifierReferences()
.Where(IsRelevantReference);

var interestingReferences = interestingDeclarations
.SelectMany(declaration => declaration.References)
.Where(reference =>
{
var letStmtContext = reference.Context.GetAncestor<VBAParser.LetStmtContext>();
return reference.IsAssignment
&& letStmtContext != null
&& letStmtContext.LET() == null
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
});
var boundIssues = boundDefaultMemberAssignments
.Select(reference => new IdentifierReferenceInspectionResult(
this,
string.Format(
InspectionResults.ImplicitDefaultMemberAssignmentInspection,
reference.Context.GetText(),
reference.Declaration.IdentifierName,
reference.Declaration.QualifiedModuleName.ToString()),
State,
reference));

return interestingReferences.Select(reference => new IdentifierReferenceInspectionResult(this,
string.Format(InspectionResults.ImplicitDefaultMemberAssignmentInspection,
reference.Declaration.IdentifierName,
reference.Declaration.AsTypeDeclaration.IdentifierName),
State,
reference));
var unboundDefaultMemberAssignments = State.DeclarationFinder
.AllUnboundDefaultMemberAccesses()
.Where(IsRelevantReference);

var unboundIssues = unboundDefaultMemberAssignments
.Select(reference => new IdentifierReferenceInspectionResult(
this,
string.Format(
InspectionResults.ImplicitDefaultMemberAssignmentInspection_Unbound,
reference.Context.GetText()),
State,
reference));

return boundIssues.Concat(unboundIssues);
}

private bool IsRelevantReference(IdentifierReference reference)
{
return reference.IsAssignment
&& reference.IsNonIndexedDefaultMemberAccess
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
}
}
}

0 comments on commit 9227d59

Please sign in to comment.