Skip to content

Commit a9f04f8

Browse files
committed
Merge branch 'next' into DefaultMemberAccessInspections
# Conflicts: # Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAssignmentInspection.cs
2 parents 7223c41 + f9140b5 commit a9f04f8

File tree

127 files changed

+1650
-889
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

127 files changed

+1650
-889
lines changed

Rubberduck.CodeAnalysis/Inspections/Abstract/IdentifierReferenceInspectionBase.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2727
var results = new List<IInspectionResult>();
2828
foreach (var moduleDeclaration in State.DeclarationFinder.UserDeclarations(DeclarationType.Module))
2929
{
30-
if (moduleDeclaration == null || moduleDeclaration.IsIgnoringInspectionResultFor(AnnotationName))
30+
if (moduleDeclaration == null)
3131
{
3232
continue;
3333
}

Rubberduck.CodeAnalysis/Inspections/Abstract/InspectionBase.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -105,7 +105,9 @@ public IEnumerable<IInspectionResult> GetInspectionResults(CancellationToken tok
105105
{
106106
var _stopwatch = new Stopwatch();
107107
_stopwatch.Start();
108-
var result = DoGetInspectionResults();
108+
var declarationFinder = State.DeclarationFinder;
109+
var result = DoGetInspectionResults()
110+
.Where(ir => !ir.IsIgnoringInspectionResult(declarationFinder));
109111
_stopwatch.Stop();
110112
_logger.Trace("Intercepted invocation of '{0}.{1}' returned {2} objects.", GetType().Name, nameof(DoGetInspectionResults), result.Count());
111113
_logger.Trace("Intercepted invocation of '{0}.{1}' ran for {2}ms", GetType().Name, nameof(DoGetInspectionResults), _stopwatch.ElapsedMilliseconds);

Rubberduck.CodeAnalysis/Inspections/Abstract/MemberAccessMayReturnNothingInspectionBase.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,9 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2929
}
3030

3131
var output = new List<IInspectionResult>();
32-
foreach (var reference in interesting.Where(use => !use.IsIgnoringInspectionResultFor(AnnotationName)))
32+
// prefilter to reduce search space
33+
var prefilteredReferences = interesting.Where(use => !use.IsIgnoringInspectionResultFor(AnnotationName));
34+
foreach (var reference in prefilteredReferences)
3335
{
3436
var access = reference.Context.GetAncestor<VBAParser.MemberAccessExprContext>();
3537
var usageContext = access.Parent is VBAParser.IndexExprContext

Rubberduck.CodeAnalysis/Inspections/Concrete/ArgumentWithIncompatibleObjectTypeInspection.cs

Lines changed: 2 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -109,7 +109,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
109109
argumentReferenceWithTypeName.argumentTypeName));
110110

111111
return offendingArguments
112-
.Where(argumentReferenceWithTypeName => !IsIgnored(argumentReferenceWithTypeName.Item1))
112+
// Ignoring the Declaration disqualifies all assignments
113+
.Where(argumentReferenceWithTypeName => !argumentReferenceWithTypeName.Item1.Declaration.IsIgnoringInspectionResultFor(AnnotationName))
113114
.Select(argumentReference => InspectionResult(argumentReference, _declarationFinderProvider));
114115
}
115116

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

170-
private bool IsIgnored(IdentifierReference assignment)
171-
{
172-
return assignment.IsIgnoringInspectionResultFor(AnnotationName)
173-
// Ignoring the Declaration disqualifies all assignments
174-
|| assignment.Declaration.IsIgnoringInspectionResultFor(AnnotationName);
175-
}
176-
177171
private IInspectionResult InspectionResult((IdentifierReference argumentReference, string argumentTypeName) argumentReferenceWithTypeName, IDeclarationFinderProvider declarationFinderProvider)
178172
{
179173
var (argumentReference, argumentTypeName) = argumentReferenceWithTypeName;

Rubberduck.CodeAnalysis/Inspections/Concrete/AssignedByValParameterInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,6 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4747
var parameters = State.DeclarationFinder.UserDeclarations(DeclarationType.Parameter)
4848
.Cast<ParameterDeclaration>()
4949
.Where(item => !item.IsByRef
50-
&& !item.IsIgnoringInspectionResultFor(AnnotationName)
5150
&& item.References.Any(reference => reference.IsAssignment));
5251

5352
return parameters

Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -71,9 +71,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
7171
}
7272

7373
return nodes
74-
.Where(issue => !issue.IsIgnoringInspectionResultFor(AnnotationName)
75-
// Ignoring the Declaration disqualifies all assignments
76-
&& !issue.Declaration.IsIgnoringInspectionResultFor(AnnotationName))
74+
// Ignoring the Declaration disqualifies all assignments
75+
.Where(issue => !issue.Declaration.IsIgnoringInspectionResultFor(AnnotationName))
7776
.Select(issue => new IdentifierReferenceInspectionResult(this, Description, State, issue))
7877
.ToList();
7978
}

Rubberduck.CodeAnalysis/Inspections/Concrete/BooleanAssignedInIfElseInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,6 @@ public BooleanAssignedInIfElseInspection(RubberduckParserState state)
4848
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4949
{
5050
return Listener.Contexts
51-
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
5251
.Select(result => new QualifiedContextInspectionResult(this,
5352
string.Format(InspectionResults.BooleanAssignedInIfElseInspection,
5453
(((VBAParser.IfStmtContext)result.Context).block().GetDescendent<VBAParser.LetStmtContext>()).lExpression().GetText().Trim()),

Rubberduck.CodeAnalysis/Inspections/Concrete/ConstantNotUsedInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -46,8 +46,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4646
{
4747
var results = State.DeclarationFinder.UserDeclarations(DeclarationType.Constant)
4848
.Where(declaration => declaration.Context != null
49-
&& !declaration.References.Any()
50-
&& !declaration.IsIgnoringInspectionResultFor(AnnotationName))
49+
&& !declaration.References.Any())
5150
.ToList();
5251

5352
return results.Select(issue =>

Rubberduck.CodeAnalysis/Inspections/Concrete/DefTypeStatementInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ public DefTypeStatementInspection(RubberduckParserState state)
4343

4444
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4545
{
46-
var results = Listener.Contexts.Where(context => !context.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
46+
var results = Listener.Contexts
4747
.Select(context => new QualifiedContextInspectionResult(this,
4848
string.Format(InspectionResults.DefTypeStatementInspection,
4949
GetTypeOfDefType(context.Context.start.Text),

Rubberduck.CodeAnalysis/Inspections/Concrete/DefaultMemberRequiredInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -69,7 +69,7 @@ protected override IEnumerable<IdentifierReference> ReferencesInModule(Qualified
6969

7070
protected override bool IsResultReference(IdentifierReference failedIndexedDefaultMemberAccess)
7171
{
72-
return !failedIndexedDefaultMemberAccess.IsIgnoringInspectionResultFor(AnnotationName);
72+
return true;
7373
}
7474

7575
protected override string ResultDescription(IdentifierReference failedIndexedDefaultMemberAccess)

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyCaseBlockInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -54,7 +54,6 @@ public EmptyCaseBlockInspection(RubberduckParserState state)
5454
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5555
{
5656
return Listener.Contexts
57-
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
5857
.Select(result => new QualifiedContextInspectionResult(this,
5958
InspectionResults.EmptyCaseBlockInspection,
6059
result));

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyDoWhileBlockInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,6 @@ public EmptyDoWhileBlockInspection(RubberduckParserState state)
4646
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4747
{
4848
return Listener.Contexts
49-
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
5049
.Select(result =>
5150
new QualifiedContextInspectionResult(this, InspectionResults.EmptyDoWhileBlockInspection, result));
5251
}

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyElseBlockInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,6 @@ public EmptyElseBlockInspection(RubberduckParserState state)
4848
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4949
{
5050
return Listener.Contexts
51-
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
5251
.Select(result => new QualifiedContextInspectionResult(this,
5352
InspectionResults.EmptyElseBlockInspection,
5453
result));

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForEachBlockInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,6 @@ public EmptyForEachBlockInspection(RubberduckParserState state)
4848
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4949
{
5050
return Listener.Contexts
51-
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
5251
.Select(result => new QualifiedContextInspectionResult(this,
5352
InspectionResults.EmptyForEachBlockInspection,
5453
result));

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForLoopBlockInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,6 @@ public EmptyForLoopBlockInspection(RubberduckParserState state)
4848
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4949
{
5050
return Listener.Contexts
51-
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
5251
.Select(result => new QualifiedContextInspectionResult(this,
5352
InspectionResults.EmptyForLoopBlockInspection,
5453
result));

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyIfBlockInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,6 @@ public EmptyIfBlockInspection(RubberduckParserState state)
4949
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5050
{
5151
return Listener.Contexts
52-
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
5352
.Select(result => new QualifiedContextInspectionResult(this,
5453
InspectionResults.EmptyIfBlockInspection,
5554
result));

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyMethodInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,6 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4343

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

4948
.Select(result => new DeclarationInspectionResult(this,

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyModuleInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -43,8 +43,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4343
.ToHashSet();
4444

4545
var emptyModuleDeclarations = State.DeclarationFinder.UserDeclarations(DeclarationType.Module)
46-
.Where(declaration => emptyModules.Contains(declaration.QualifiedName.QualifiedModuleName)
47-
&& !declaration.IsIgnoringInspectionResultFor(AnnotationName));
46+
.Where(declaration => emptyModules.Contains(declaration.QualifiedName.QualifiedModuleName));
4847

4948
return emptyModuleDeclarations.Select(declaration =>
5049
new DeclarationInspectionResult(this, string.Format(InspectionResults.EmptyModuleInspection, declaration.IdentifierName), declaration));

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyStringLiteralInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,6 @@ public EmptyStringLiteralInspection(RubberduckParserState state)
5050
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5151
{
5252
return Listener.Contexts
53-
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
5453
.Select(result => new QualifiedContextInspectionResult(this,
5554
InspectionResults.EmptyStringLiteralInspection,
5655
result));

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyWhileWendBlockInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,6 @@ public EmptyWhileWendBlockInspection(RubberduckParserState state)
4646
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4747
{
4848
return Listener.Contexts
49-
.Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName))
5049
.Select(result => new QualifiedContextInspectionResult(this,
5150
InspectionResults.EmptyWhileWendBlockInspection,
5251
result));

Rubberduck.CodeAnalysis/Inspections/Concrete/EncapsulatePublicFieldInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -40,8 +40,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4040
{
4141
// we're creating a public field for every control on a form, needs to be ignored.
4242
var fields = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
43-
.Where(item => !item.IsIgnoringInspectionResultFor(AnnotationName)
44-
&& item.Accessibility == Accessibility.Public
43+
.Where(item => item.Accessibility == Accessibility.Public
4544
&& (item.DeclarationType != DeclarationType.Control))
4645
.ToList();
4746

Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ApplicationWorksheetFunctionInspection.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -75,6 +75,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
7575
members.Contains(decl.IdentifierName));
7676

7777
return from usage in usages
78+
// filtering on references isn't the default ignore filtering
7879
from reference in usage.References.Where(use => !use.IsIgnoringInspectionResultFor(AnnotationName))
7980
let qualifiedSelection = new QualifiedSelection(reference.QualifiedModuleName, reference.Selection)
8081
select new IdentifierReferenceInspectionResult(this,

Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ExcelUdfNameIsValidCellReferenceInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
6060

6161
return (from function in candidates.Where(decl => ValidCellIdRegex.IsMatch(decl.IdentifierName))
6262
let row = Convert.ToUInt32(ValidCellIdRegex.Matches(function.IdentifierName)[0].Groups["Row"].Value)
63-
where row > 0 && row <= MaximumExcelRows && !function.IsIgnoringInspectionResultFor(AnnotationName)
63+
where row > 0 && row <= MaximumExcelRows
6464
select new DeclarationInspectionResult(this,
6565
string.Format(InspectionResults.ExcelUdfNameIsValidCellReferenceInspection, function.IdentifierName),
6666
function))

Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ImplicitActiveSheetReferenceInspection.cs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -67,12 +67,10 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
6767

6868
return members
6969
.SelectMany(declaration => declaration.References)
70-
.Where(issue => !issue.IsIgnoringInspectionResultFor(AnnotationName))
7170
.Select(issue => new IdentifierReferenceInspectionResult(this,
7271
string.Format(InspectionResults.ImplicitActiveSheetReferenceInspection, issue.Declaration.IdentifierName),
7372
State,
74-
issue))
75-
.ToList();
73+
issue));
7674
}
7775
}
7876
}

Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ImplicitActiveWorkbookReferenceInspection.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -66,6 +66,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
6666
.Where(x => InterestingMembers.Contains(x.IdentifierName) && InterestingClasses.Contains(x.ParentDeclaration?.IdentifierName))
6767
.ToList();
6868

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

Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/SheetAccessedUsingStringInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -73,8 +73,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
7373
.ToList();
7474

7575
var references = targetProperties.SelectMany(declaration => declaration.References
76-
.Where(reference => !reference.IsIgnoringInspectionResultFor(AnnotationName) &&
77-
IsAccessedWithStringLiteralParameter(reference))
76+
.Where(reference => IsAccessedWithStringLiteralParameter(reference))
7877
.Select(reference => new IdentifierReferenceInspectionResult(this,
7978
InspectionResults.SheetAccessedUsingStringInspection, State, reference)));
8079

Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueNotUsedInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -57,8 +57,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5757
var interfaceImplementationMembers = State.DeclarationFinder.FindAllInterfaceImplementingMembers();
5858
var functions = State.DeclarationFinder
5959
.UserDeclarations(DeclarationType.Function)
60-
.Where(item => !item.IsIgnoringInspectionResultFor(AnnotationName) &&
61-
item.References.Any(r => !IsReturnStatement(item, r) && !r.IsAssignment))
60+
.Where(item => item.References.Any(r => !IsReturnStatement(item, r) && !r.IsAssignment))
6261
.ToList();
6362
var interfaceMemberIssues = GetInterfaceMemberIssues(interfaceMembers);
6463
var nonInterfaceFunctions = functions.Except(interfaceMembers.Union(interfaceImplementationMembers));

Rubberduck.CodeAnalysis/Inspections/Concrete/HungarianNotationInspection.cs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -150,12 +150,11 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
150150
var whitelistedNames = settings.WhitelistedIdentifiers.Select(s => s.Identifier).ToList();
151151

152152
var hungarians = UserDeclarations
153-
.Where(declaration => !whitelistedNames.Contains(declaration.IdentifierName) &&
154-
TargetDeclarationTypes.Contains(declaration.DeclarationType) &&
155-
!IgnoredProcedureTypes.Contains(declaration.DeclarationType) &&
156-
!IgnoredProcedureTypes.Contains(declaration.ParentDeclaration.DeclarationType) &&
157-
HungarianIdentifierRegex.IsMatch(declaration.IdentifierName) &&
158-
!declaration.IsIgnoringInspectionResultFor(AnnotationName))
153+
.Where(declaration => !whitelistedNames.Contains(declaration.IdentifierName)
154+
&& TargetDeclarationTypes.Contains(declaration.DeclarationType)
155+
&& !IgnoredProcedureTypes.Contains(declaration.DeclarationType)
156+
&& !IgnoredProcedureTypes.Contains(declaration.ParentDeclaration.DeclarationType)
157+
&& HungarianIdentifierRegex.IsMatch(declaration.IdentifierName))
159158
.Select(issue => new DeclarationInspectionResult(this,
160159
string.Format(Resources.Inspections.InspectionResults.IdentifierNameInspection,
161160
RubberduckUI.ResourceManager.GetString($"DeclarationType_{issue.DeclarationType}", CultureInfo.CurrentUICulture),

0 commit comments

Comments
 (0)