Skip to content

Commit

Permalink
Merge pull request #5146 from MDoerner/FailedLetCoercionOnObjectInspe…
Browse files Browse the repository at this point in the history
…ction

New Inspections for failed default member resolutions
  • Loading branch information
retailcoder committed Sep 15, 2019
2 parents 225b09b + a39376f commit 38c928e
Show file tree
Hide file tree
Showing 41 changed files with 4,474 additions and 331 deletions.
@@ -0,0 +1,101 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Inspections.Extensions;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.Inspections;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Locates indexed default member calls for which the corresponding object does not have a suitable suitable default member.
/// </summary>
/// <why>
/// The VBA compiler does not check whether the necessary default member is present. Instead there is a runtime error whenever the runtime type fails to have the default member.
/// </why>
/// <example hasResult="true">
/// <![CDATA[
/// Class1:
///
/// Public Function Foo(index As Long) As Long
/// 'No default member attribute
/// End Function
///
/// ------------------------------
/// Module1:
///
/// Public Sub DoIt()
/// Dim cls As Class1
/// Dim bar As Variant
/// Set cls = New Class1
/// bar = cls(0)
/// End Sub
/// ]]>
/// </example>
/// <example hasResult="false">
/// <![CDATA[
/// Class1:
///
/// Public Function Foo(index As Long) As Long
/// Attribute Foo.UserMemId = 0
/// End Function
///
/// ------------------------------
/// Module1:
///
/// Public Sub DoIt()
/// Dim cls As Class1
/// Dim bar As Variant
/// Set cls = New Class1
/// bar = cls(0)
/// End Sub
/// ]]>
/// </example>
public class DefaultMemberRequiredInspection : InspectionBase
{
private readonly IDeclarationFinderProvider _declarationFinderProvider;

public DefaultMemberRequiredInspection(RubberduckParserState state)
: base(state)
{
_declarationFinderProvider = state;

//This will most likely cause a runtime error. The exceptions are rare and should be refactored or made explicit with an @Ignore annotation.
Severity = CodeInspectionSeverity.Error;
}

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var finder = _declarationFinderProvider.DeclarationFinder;

var failedIndexedDefaultMemberAccesses = finder.FailedIndexedDefaultMemberAccesses();
return failedIndexedDefaultMemberAccesses
.Where(failedIndexedDefaultMemberAccess => !IsIgnored(failedIndexedDefaultMemberAccess))
.Select(failedIndexedDefaultMemberAccess => InspectionResult(failedIndexedDefaultMemberAccess, _declarationFinderProvider));
}

private bool IsIgnored(IdentifierReference assignment)
{
return assignment.IsIgnoringInspectionResultFor(AnnotationName);
}

private IInspectionResult InspectionResult(IdentifierReference failedCoercion, IDeclarationFinderProvider declarationFinderProvider)
{
return new IdentifierReferenceInspectionResult(this,
ResultDescription(failedCoercion),
declarationFinderProvider,
failedCoercion);
}

private string ResultDescription(IdentifierReference failedIndexedDefaultMemberAccess)
{
var expression = failedIndexedDefaultMemberAccess.IdentifierName;
var typeName = failedIndexedDefaultMemberAccess.Declaration?.FullAsTypeName;
return string.Format(InspectionResults.DefaultMemberRequiredInspection, expression, typeName);
}
}
}
Expand Up @@ -44,7 +44,7 @@ public MemberNotOnInterfaceInspection(RubberduckParserState state)

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var unresolved = State.DeclarationFinder.UnresolvedMemberDeclarations
var unresolved = State.DeclarationFinder.UnresolvedMemberDeclarations()
.Where(decl => !decl.IsIgnoringInspectionResultFor(AnnotationName)).ToList();

var targets = Declarations.Where(decl => decl.AsTypeDeclaration != null &&
Expand Down
@@ -1,12 +1,18 @@
using System.Collections.Generic;
using System;
using System.Collections.Generic;
using System.Linq;
using Antlr4.Runtime;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Resources.Inspections;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Inspections.Inspections.Extensions;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.VBEditor;

namespace Rubberduck.Inspections.Concrete
{
Expand Down Expand Up @@ -42,30 +48,78 @@ public ObjectVariableNotSetInspection(RubberduckParserState state)

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var finder = State.DeclarationFinder;

return InterestingReferences().Select(reference =>
new IdentifierReferenceInspectionResult(this,
string.Format(InspectionResults.ObjectVariableNotSetInspection, reference.Declaration.IdentifierName),
State, reference));
var failedLetResolutionResults = FailedLetResolutionResults(finder);

return failedLetResolutionResults
.Select(reference =>
new IdentifierReferenceInspectionResult(
this,
string.Format(InspectionResults.ObjectVariableNotSetInspection, reference.IdentifierName),
State,
reference));
}

private IEnumerable<IdentifierReference> InterestingReferences()
private IEnumerable<IdentifierReference> FailedLetResolutionResults(DeclarationFinder finder)
{
var result = new List<IdentifierReference>();
foreach (var moduleReferences in State.DeclarationFinder.IdentifierReferences())
var results = new List<IdentifierReference>();
foreach (var moduleDeclaration in finder.UserDeclarations(DeclarationType.Module))
{
var module = State.DeclarationFinder.ModuleDeclaration(moduleReferences.Key);
if (module == null || !module.IsUserDefined || module.IsIgnoringInspectionResultFor(AnnotationName))
if (moduleDeclaration == null || moduleDeclaration.IsIgnoringInspectionResultFor(AnnotationName))
{
// module isn't user code (?), or this inspection is ignored at module-level
continue;
}

result.AddRange(moduleReferences.Value.Where(reference => !reference.IsSetAssignment
&& VariableRequiresSetAssignmentEvaluator.RequiresSetAssignment(reference, State)));
var module = moduleDeclaration.QualifiedModuleName;
var failedLetCoercionAssignmentsInModule = FailedLetResolutionAssignments(module, finder);
var possiblyObjectLhsLetAssignmentsWithFailedLetResolutionOnRhs = PossiblyObjectLhsLetAssignmentsWithNonValueOnRhs(module, finder);
results.AddRange(failedLetCoercionAssignmentsInModule);
results.AddRange(possiblyObjectLhsLetAssignmentsWithFailedLetResolutionOnRhs);
}

return result.Where(reference => !reference.IsIgnoringInspectionResultFor(AnnotationName));
return results.Where(reference => !reference.IsIgnoringInspectionResultFor(AnnotationName));
}

private static IEnumerable<IdentifierReference> FailedLetResolutionAssignments(QualifiedModuleName module, DeclarationFinder finder)
{
return finder.FailedLetCoercions(module)
.Where(reference => reference.IsAssignment);
}

private static IEnumerable<IdentifierReference> PossiblyObjectLhsLetAssignmentsWithNonValueOnRhs(QualifiedModuleName module, DeclarationFinder finder)
{
return PossiblyObjectLhsLetAssignments(module, finder)
.Where(tpl => finder.FailedLetCoercions(module)
.Any(reference => reference.Selection.Equals(tpl.rhs.GetSelection()))
|| Tokens.Nothing.Equals(tpl.rhs.GetText(), StringComparison.InvariantCultureIgnoreCase))
.Select(tpl => tpl.assignment);
}

private static IEnumerable<(IdentifierReference assignment, ParserRuleContext rhs)> PossiblyObjectLhsLetAssignments(QualifiedModuleName module, DeclarationFinder finder)
{
return PossiblyObjectNonSetAssignments(module, finder)
.Select(reference => (reference, RhsOfLetAssignment(reference)))
.Where(tpl => tpl.Item2 != null);
}

private static ParserRuleContext RhsOfLetAssignment(IdentifierReference letAssignment)
{
var letStatement = letAssignment.Context.Parent as VBAParser.LetStmtContext;
return letStatement?.expression();
}

private static IEnumerable<IdentifierReference> PossiblyObjectNonSetAssignments(QualifiedModuleName module, DeclarationFinder finder)
{
var assignments = finder.IdentifierReferences(module)
.Where(reference => reference.IsAssignment
&& !reference.IsSetAssignment
&& (reference.IsNonIndexedDefaultMemberAccess
|| Tokens.Variant.Equals(reference.Declaration.AsTypeName, StringComparison.InvariantCultureIgnoreCase)));
var unboundAssignments = finder.UnboundDefaultMemberAccesses(module)
.Where(reference => reference.IsAssignment);

return assignments.Concat(unboundAssignments);
}
}
}
@@ -0,0 +1,99 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Inspections.Extensions;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.Inspections;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Locates places in which a procedure needs to be called but an object variables has been provided that does not have a suitable default member.
/// </summary>
/// <why>
/// The VBA compiler does not check whether the necessary default member is present. Instead there is a runtime error whenever the runtime type fails to have the default member.
/// </why>
/// <example hasResult="true">
/// <![CDATA[
/// Class1:
///
/// Public Sub Foo()
/// 'No default member attribute
/// End Sub
///
/// ------------------------------
/// Module1:
///
/// Public Sub DoIt()
/// Dim cls As Class1
/// Set cls = New Class1
/// cls
/// End Sub
/// ]]>
/// </example>
/// <example hasResult="false">
/// <![CDATA[
/// Class1:
///
/// Public Sub Foo()
/// Attribute Foo.UserMemId = 0
/// End Sub
///
/// ------------------------------
/// Module1:
///
/// Public Sub DoIt()
/// Dim cls As Class1
/// Set cls = New Class1
/// cls
/// End Sub
/// ]]>
/// </example>
public class ProcedureRequiredInspection : InspectionBase
{
private readonly IDeclarationFinderProvider _declarationFinderProvider;

public ProcedureRequiredInspection(RubberduckParserState state)
: base(state)
{
_declarationFinderProvider = state;

//This will most likely cause a runtime error. The exceptions are rare and should be refactored or made explicit with an @Ignore annotation.
Severity = CodeInspectionSeverity.Error;
}

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var finder = _declarationFinderProvider.DeclarationFinder;

var failedProcedureCoercions = finder.FailedProcedureCoercions();
return failedProcedureCoercions
.Where(failedCoercion => !IsIgnored(failedCoercion))
.Select(failedCoercion => InspectionResult(failedCoercion, _declarationFinderProvider));
}

private bool IsIgnored(IdentifierReference assignment)
{
return assignment.IsIgnoringInspectionResultFor(AnnotationName);
}

private IInspectionResult InspectionResult(IdentifierReference failedCoercion, IDeclarationFinderProvider declarationFinderProvider)
{
return new IdentifierReferenceInspectionResult(this,
ResultDescription(failedCoercion),
declarationFinderProvider,
failedCoercion);
}

private string ResultDescription(IdentifierReference failedCoercion)
{
var expression = failedCoercion.IdentifierName;
var typeName = failedCoercion.Declaration?.FullAsTypeName;
return string.Format(InspectionResults.ProcedureRequiredInspection, expression, typeName);
}
}
}

0 comments on commit 38c928e

Please sign in to comment.