Skip to content

Commit

Permalink
Merge branch 'next' into DefaultMemberAccessInspections
Browse files Browse the repository at this point in the history
# Conflicts:
#	Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAssignmentInspection.cs
  • Loading branch information
MDoerner committed Oct 7, 2019
2 parents 7223c41 + f9140b5 commit a9f04f8
Show file tree
Hide file tree
Showing 127 changed files with 1,650 additions and 889 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
var results = new List<IInspectionResult>();
foreach (var moduleDeclaration in State.DeclarationFinder.UserDeclarations(DeclarationType.Module))
{
if (moduleDeclaration == null || moduleDeclaration.IsIgnoringInspectionResultFor(AnnotationName))
if (moduleDeclaration == null)
{
continue;
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,9 @@ public IEnumerable<IInspectionResult> GetInspectionResults(CancellationToken tok
{
var _stopwatch = new Stopwatch();
_stopwatch.Start();
var result = DoGetInspectionResults();
var declarationFinder = State.DeclarationFinder;
var result = DoGetInspectionResults()
.Where(ir => !ir.IsIgnoringInspectionResult(declarationFinder));
_stopwatch.Stop();
_logger.Trace("Intercepted invocation of '{0}.{1}' returned {2} objects.", GetType().Name, nameof(DoGetInspectionResults), result.Count());
_logger.Trace("Intercepted invocation of '{0}.{1}' ran for {2}ms", GetType().Name, nameof(DoGetInspectionResults), _stopwatch.ElapsedMilliseconds);
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,9 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
}

var output = new List<IInspectionResult>();
foreach (var reference in interesting.Where(use => !use.IsIgnoringInspectionResultFor(AnnotationName)))
// prefilter to reduce search space
var prefilteredReferences = interesting.Where(use => !use.IsIgnoringInspectionResultFor(AnnotationName));
foreach (var reference in prefilteredReferences)
{
var access = reference.Context.GetAncestor<VBAParser.MemberAccessExprContext>();
var usageContext = access.Parent is VBAParser.IndexExprContext
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -109,7 +109,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
argumentReferenceWithTypeName.argumentTypeName));

return offendingArguments
.Where(argumentReferenceWithTypeName => !IsIgnored(argumentReferenceWithTypeName.Item1))
// Ignoring the Declaration disqualifies all assignments
.Where(argumentReferenceWithTypeName => !argumentReferenceWithTypeName.Item1.Declaration.IsIgnoringInspectionResultFor(AnnotationName))
.Select(argumentReference => InspectionResult(argumentReference, _declarationFinderProvider));
}

Expand Down Expand Up @@ -167,13 +168,6 @@ private bool HasSubType(Declaration declaration, string typeName)
return classType.Supertypes.Select(supertype => supertype.QualifiedModuleName.ToString()).Contains(typeName);
}

private bool IsIgnored(IdentifierReference assignment)
{
return assignment.IsIgnoringInspectionResultFor(AnnotationName)
// Ignoring the Declaration disqualifies all assignments
|| assignment.Declaration.IsIgnoringInspectionResultFor(AnnotationName);
}

private IInspectionResult InspectionResult((IdentifierReference argumentReference, string argumentTypeName) argumentReferenceWithTypeName, IDeclarationFinderProvider declarationFinderProvider)
{
var (argumentReference, argumentTypeName) = argumentReferenceWithTypeName;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,6 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
var parameters = State.DeclarationFinder.UserDeclarations(DeclarationType.Parameter)
.Cast<ParameterDeclaration>()
.Where(item => !item.IsByRef
&& !item.IsIgnoringInspectionResultFor(AnnotationName)
&& item.References.Any(reference => reference.IsAssignment));

return parameters
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -71,9 +71,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
}

return nodes
.Where(issue => !issue.IsIgnoringInspectionResultFor(AnnotationName)
// Ignoring the Declaration disqualifies all assignments
&& !issue.Declaration.IsIgnoringInspectionResultFor(AnnotationName))
// Ignoring the Declaration disqualifies all assignments
.Where(issue => !issue.Declaration.IsIgnoringInspectionResultFor(AnnotationName))
.Select(issue => new IdentifierReferenceInspectionResult(this, Description, State, issue))
.ToList();
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,6 @@ public BooleanAssignedInIfElseInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
return Listener.Contexts
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
.Select(result => new QualifiedContextInspectionResult(this,
string.Format(InspectionResults.BooleanAssignedInIfElseInspection,
(((VBAParser.IfStmtContext)result.Context).block().GetDescendent<VBAParser.LetStmtContext>()).lExpression().GetText().Trim()),
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -46,8 +46,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var results = State.DeclarationFinder.UserDeclarations(DeclarationType.Constant)
.Where(declaration => declaration.Context != null
&& !declaration.References.Any()
&& !declaration.IsIgnoringInspectionResultFor(AnnotationName))
&& !declaration.References.Any())
.ToList();

return results.Select(issue =>
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ public DefTypeStatementInspection(RubberduckParserState state)

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var results = Listener.Contexts.Where(context => !context.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
var results = Listener.Contexts
.Select(context => new QualifiedContextInspectionResult(this,
string.Format(InspectionResults.DefTypeStatementInspection,
GetTypeOfDefType(context.Context.start.Text),
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@ protected override IEnumerable<IdentifierReference> ReferencesInModule(Qualified

protected override bool IsResultReference(IdentifierReference failedIndexedDefaultMemberAccess)
{
return !failedIndexedDefaultMemberAccess.IsIgnoringInspectionResultFor(AnnotationName);
return true;
}

protected override string ResultDescription(IdentifierReference failedIndexedDefaultMemberAccess)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,6 @@ public EmptyCaseBlockInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
return Listener.Contexts
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
.Select(result => new QualifiedContextInspectionResult(this,
InspectionResults.EmptyCaseBlockInspection,
result));
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,6 @@ public EmptyDoWhileBlockInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
return Listener.Contexts
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
.Select(result =>
new QualifiedContextInspectionResult(this, InspectionResults.EmptyDoWhileBlockInspection, result));
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,6 @@ public EmptyElseBlockInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
return Listener.Contexts
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
.Select(result => new QualifiedContextInspectionResult(this,
InspectionResults.EmptyElseBlockInspection,
result));
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,6 @@ public EmptyForEachBlockInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
return Listener.Contexts
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
.Select(result => new QualifiedContextInspectionResult(this,
InspectionResults.EmptyForEachBlockInspection,
result));
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,6 @@ public EmptyForLoopBlockInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
return Listener.Contexts
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
.Select(result => new QualifiedContextInspectionResult(this,
InspectionResults.EmptyForLoopBlockInspection,
result));
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,6 @@ public EmptyIfBlockInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
return Listener.Contexts
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
.Select(result => new QualifiedContextInspectionResult(this,
InspectionResults.EmptyIfBlockInspection,
result));
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,6 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()

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

.Select(result => new DeclarationInspectionResult(this,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -43,8 +43,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
.ToHashSet();

var emptyModuleDeclarations = State.DeclarationFinder.UserDeclarations(DeclarationType.Module)
.Where(declaration => emptyModules.Contains(declaration.QualifiedName.QualifiedModuleName)
&& !declaration.IsIgnoringInspectionResultFor(AnnotationName));
.Where(declaration => emptyModules.Contains(declaration.QualifiedName.QualifiedModuleName));

return emptyModuleDeclarations.Select(declaration =>
new DeclarationInspectionResult(this, string.Format(InspectionResults.EmptyModuleInspection, declaration.IdentifierName), declaration));
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,6 @@ public EmptyStringLiteralInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
return Listener.Contexts
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
.Select(result => new QualifiedContextInspectionResult(this,
InspectionResults.EmptyStringLiteralInspection,
result));
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,6 @@ public EmptyWhileWendBlockInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
return Listener.Contexts
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
.Select(result => new QualifiedContextInspectionResult(this,
InspectionResults.EmptyWhileWendBlockInspection,
result));
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -40,8 +40,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
// we're creating a public field for every control on a form, needs to be ignored.
var fields = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
.Where(item => !item.IsIgnoringInspectionResultFor(AnnotationName)
&& item.Accessibility == Accessibility.Public
.Where(item => item.Accessibility == Accessibility.Public
&& (item.DeclarationType != DeclarationType.Control))
.ToList();

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -75,6 +75,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
members.Contains(decl.IdentifierName));

return from usage in usages
// filtering on references isn't the default ignore filtering
from reference in usage.References.Where(use => !use.IsIgnoringInspectionResultFor(AnnotationName))
let qualifiedSelection = new QualifiedSelection(reference.QualifiedModuleName, reference.Selection)
select new IdentifierReferenceInspectionResult(this,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()

return (from function in candidates.Where(decl => ValidCellIdRegex.IsMatch(decl.IdentifierName))
let row = Convert.ToUInt32(ValidCellIdRegex.Matches(function.IdentifierName)[0].Groups["Row"].Value)
where row > 0 && row <= MaximumExcelRows && !function.IsIgnoringInspectionResultFor(AnnotationName)
where row > 0 && row <= MaximumExcelRows
select new DeclarationInspectionResult(this,
string.Format(InspectionResults.ExcelUdfNameIsValidCellReferenceInspection, function.IdentifierName),
function))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -67,12 +67,10 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()

return members
.SelectMany(declaration => declaration.References)
.Where(issue => !issue.IsIgnoringInspectionResultFor(AnnotationName))
.Select(issue => new IdentifierReferenceInspectionResult(this,
string.Format(InspectionResults.ImplicitActiveSheetReferenceInspection, issue.Declaration.IdentifierName),
State,
issue))
.ToList();
issue));
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -66,6 +66,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
.Where(x => InterestingMembers.Contains(x.IdentifierName) && InterestingClasses.Contains(x.ParentDeclaration?.IdentifierName))
.ToList();

// only inspects references, must filter ignores manually, because default filtering doesn't work here
var members = targetProperties.SelectMany(item =>
item.References.Where(reference => !reference.IsIgnoringInspectionResultFor(AnnotationName)));

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -73,8 +73,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
.ToList();

var references = targetProperties.SelectMany(declaration => declaration.References
.Where(reference => !reference.IsIgnoringInspectionResultFor(AnnotationName) &&
IsAccessedWithStringLiteralParameter(reference))
.Where(reference => IsAccessedWithStringLiteralParameter(reference))
.Select(reference => new IdentifierReferenceInspectionResult(this,
InspectionResults.SheetAccessedUsingStringInspection, State, reference)));

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -57,8 +57,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
var interfaceImplementationMembers = State.DeclarationFinder.FindAllInterfaceImplementingMembers();
var functions = State.DeclarationFinder
.UserDeclarations(DeclarationType.Function)
.Where(item => !item.IsIgnoringInspectionResultFor(AnnotationName) &&
item.References.Any(r => !IsReturnStatement(item, r) && !r.IsAssignment))
.Where(item => item.References.Any(r => !IsReturnStatement(item, r) && !r.IsAssignment))
.ToList();
var interfaceMemberIssues = GetInterfaceMemberIssues(interfaceMembers);
var nonInterfaceFunctions = functions.Except(interfaceMembers.Union(interfaceImplementationMembers));
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -150,12 +150,11 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
var whitelistedNames = settings.WhitelistedIdentifiers.Select(s => s.Identifier).ToList();

var hungarians = UserDeclarations
.Where(declaration => !whitelistedNames.Contains(declaration.IdentifierName) &&
TargetDeclarationTypes.Contains(declaration.DeclarationType) &&
!IgnoredProcedureTypes.Contains(declaration.DeclarationType) &&
!IgnoredProcedureTypes.Contains(declaration.ParentDeclaration.DeclarationType) &&
HungarianIdentifierRegex.IsMatch(declaration.IdentifierName) &&
!declaration.IsIgnoringInspectionResultFor(AnnotationName))
.Where(declaration => !whitelistedNames.Contains(declaration.IdentifierName)
&& TargetDeclarationTypes.Contains(declaration.DeclarationType)
&& !IgnoredProcedureTypes.Contains(declaration.DeclarationType)
&& !IgnoredProcedureTypes.Contains(declaration.ParentDeclaration.DeclarationType)
&& HungarianIdentifierRegex.IsMatch(declaration.IdentifierName))
.Select(issue => new DeclarationInspectionResult(this,
string.Format(Resources.Inspections.InspectionResults.IdentifierNameInspection,
RubberduckUI.ResourceManager.GetString($"DeclarationType_{issue.DeclarationType}", CultureInfo.CurrentUICulture),
Expand Down

0 comments on commit a9f04f8

Please sign in to comment.