Skip to content

Commit

Permalink
Merge pull request #5234 from MDoerner/FixUntypedFunctionInspection
Browse files Browse the repository at this point in the history
Fix untyped function inspection
  • Loading branch information
retailcoder committed Oct 18, 2019
2 parents 61c6db9 + d7ee479 commit 5fcc213
Show file tree
Hide file tree
Showing 5 changed files with 112 additions and 706 deletions.
Expand Up @@ -6,8 +6,11 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Inspections.Inspections.Extensions;
using Rubberduck.Common;
using Rubberduck.Inspections.Inspections.Extensions;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Parsing.VBA.Extensions;
using Rubberduck.VBEditor;

namespace Rubberduck.Inspections.Concrete
{
Expand Down Expand Up @@ -39,19 +42,48 @@ public EmptyMethodInspection(RubberduckParserState state)

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var allInterfaces = new HashSet<ClassModuleDeclaration>(State.DeclarationFinder.FindAllUserInterfaces());

return State.DeclarationFinder.UserDeclarations(DeclarationType.Member)
.Where(member => !allInterfaces.Any(userInterface => userInterface.QualifiedModuleName == member.QualifiedModuleName)
&& !(member is ModuleBodyElementDeclaration mbe && mbe.Block.ContainsExecutableStatements()))

.Select(result => new DeclarationInspectionResult(this,
string.Format(InspectionResults.EmptyMethodInspection,
Resources.RubberduckUI.ResourceManager
.GetString("DeclarationType_" + result.DeclarationType)
.Capitalize(),
result.IdentifierName),
result));
var finder = State.DeclarationFinder;

var userInterfaces = UserInterfaces(finder);
var emptyMethods = EmptyNonInterfaceMethods(finder, userInterfaces);

return emptyMethods.Select(Result);
}

private static ICollection<QualifiedModuleName> UserInterfaces(DeclarationFinder finder)
{
return finder
.FindAllUserInterfaces()
.Select(decl => decl.QualifiedModuleName)
.ToHashSet();
}

private static IEnumerable<Declaration> EmptyNonInterfaceMethods(DeclarationFinder finder, ICollection<QualifiedModuleName> userInterfaces)
{
return finder
.UserDeclarations(DeclarationType.Member)
.Where(member => !userInterfaces.Contains(member.QualifiedModuleName)
&& member is ModuleBodyElementDeclaration moduleBodyElement
&& !moduleBodyElement.Block.ContainsExecutableStatements());
}

private IInspectionResult Result(Declaration member)
{
return new DeclarationInspectionResult(
this,
ResultDescription(member),
member);
}

private static string ResultDescription(Declaration member)
{
var identifierName = member.IdentifierName;
var declarationType = member.DeclarationType.ToLocalizedString();

return string.Format(
InspectionResults.EmptyMethodInspection,
declarationType,
identifierName);
}
}
}
Expand Up @@ -6,7 +6,8 @@
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Resources.Inspections;
using Rubberduck.Parsing.VBA;
using Rubberduck.Inspections.Inspections.Extensions;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA.DeclarationCaching;

namespace Rubberduck.Inspections.Concrete
{
Expand Down Expand Up @@ -36,7 +37,7 @@ public sealed class UntypedFunctionUsageInspection : InspectionBase
public UntypedFunctionUsageInspection(RubberduckParserState state)
: base(state) { }

private readonly string[] _tokens = {
private readonly HashSet<string> _tokens = new HashSet<string>{
Tokens.Error,
Tokens.Hex,
Tokens.Oct,
Expand Down Expand Up @@ -64,17 +65,46 @@ public UntypedFunctionUsageInspection(RubberduckParserState state)

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var declarations = BuiltInDeclarations
.Where(item =>
_tokens.Any(token => item.IdentifierName == token || item.IdentifierName == "_B_var_" + token) &&
item.Scope.StartsWith("VBE7.DLL;"));
var finder = State.DeclarationFinder;

return declarations.SelectMany(declaration => declaration.References
.Where(item => _tokens.Contains(item.IdentifierName))
.Select(item => new IdentifierReferenceInspectionResult(this,
string.Format(InspectionResults.UntypedFunctionUsageInspection, item.Declaration.IdentifierName),
State,
item)));
var declarationsToConsider = BuiltInVariantStringFunctionsWithStringTypedVersion(finder);

return declarationsToConsider
.SelectMany(NonStringHintedReferences)
.Select(Result);
}

private IEnumerable<Declaration> BuiltInVariantStringFunctionsWithStringTypedVersion(DeclarationFinder finder)
{
return finder
.BuiltInDeclarations(DeclarationType.Member)
.Where(item => (_tokens.Contains(item.IdentifierName)
|| item.IdentifierName.StartsWith("_B_var_")
&& _tokens.Contains(item.IdentifierName.Substring("_B_var_".Length)))
&& item.Scope.StartsWith("VBE7.DLL;"));
}

private IEnumerable<IdentifierReference> NonStringHintedReferences(Declaration declaration)
{
return declaration.References
.Where(item => _tokens.Contains(item.IdentifierName));
}

private IInspectionResult Result(IdentifierReference reference)
{
return new IdentifierReferenceInspectionResult(
this,
ResultDescription(reference),
State,
reference);
}

private static string ResultDescription(IdentifierReference reference)
{
var declarationName = reference.Declaration.IdentifierName;
return string.Format(
InspectionResults.UntypedFunctionUsageInspection,
declarationName);
}
}
}
Expand Up @@ -124,7 +124,7 @@ public BoundExpressionVisitor(DeclarationFinder declarationFinder)
{
var callSiteContext = expression.Context;
var callee = expression.ReferencedDeclaration;
var identifier = callee.IdentifierName;
var identifier = WithEnclosingBracketsRemoved(callSiteContext.GetText());
var selection = callSiteContext.GetSelection();
expression.ReferencedDeclaration.AddReference(
module,
Expand Down Expand Up @@ -164,7 +164,7 @@ private IEnumerable<IParseTreeAnnotation> FindIdentifierAnnotations(QualifiedMod

var callSiteContext = expression.UnrestrictedNameContext;
var callee = expression.ReferencedDeclaration;
var identifier = callee.IdentifierName;
var identifier = WithEnclosingBracketsRemoved(callSiteContext.GetText());
var selection = callSiteContext.GetSelection();
expression.ReferencedDeclaration.AddReference(
module,
Expand All @@ -180,6 +180,16 @@ private IEnumerable<IParseTreeAnnotation> FindIdentifierAnnotations(QualifiedMod
isSetAssignment);
}

private static string WithEnclosingBracketsRemoved(string identifierName)
{
if (identifierName.StartsWith("[") && identifierName.EndsWith("]"))
{
return identifierName.Substring(1, identifierName.Length - 2);
}

return identifierName;
}

private void Visit(
ObjectPrintExpression expression,
QualifiedModuleName module,
Expand Down
11 changes: 11 additions & 0 deletions RubberduckTests/Inspections/EmptyMethodInspectionTests.cs
Expand Up @@ -118,6 +118,17 @@ Sub Foo()
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

[Test]
[Category("Inspections")]
public void EmptyMethod_DeclareStatement_NoResult()
{
string inputCode =
$@"
Private Declare PtrSafe Function GetKeyState Lib ""user32.dll"" (ByVal nVirtKey As Long) As Integer
";
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
}

private void CheckActualEmptyBlockCountEqualsExpected(string interfaceCode, string concreteCode, int expectedCount)
{
var builder = new MockVbeBuilder();
Expand Down

0 comments on commit 5fcc213

Please sign in to comment.