Skip to content

Commit e5f460e

Browse files
committed
Merge branch 'next' of https://github.com/rubberduck-vba/Rubberduck into MiscBugFixes
2 parents 7419dc6 + 5fcc213 commit e5f460e

File tree

275 files changed

+7807
-5256
lines changed

Some content is hidden

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

275 files changed

+7807
-5256
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/Abstract/QuickFixBase.cs

Lines changed: 16 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
using System;
22
using System.Collections.Generic;
3+
using System.Diagnostics;
34
using System.Linq;
45
using NLog;
56
using Rubberduck.Parsing.Inspections.Abstract;
@@ -24,17 +25,28 @@ public void RegisterInspections(params Type[] inspections)
2425
{
2526
if (!inspections.All(s => s.GetInterfaces().Any(a => a == typeof(IInspection))))
2627
{
27-
#if DEBUG
28-
throw new ArgumentException($"Parameters must implement {nameof(IInspection)}", nameof(inspections));
29-
#else
28+
var dieNow = false;
29+
MustThrowException(ref dieNow);
30+
if (dieNow)
31+
{
32+
throw new ArgumentException($"Parameters must implement {nameof(IInspection)}",
33+
nameof(inspections));
34+
}
35+
3036
inspections.Where(s => s.GetInterfaces().All(i => i != typeof(IInspection))).ToList()
3137
.ForEach(i => Logger.Error($"Type {i.Name} does not implement {nameof(IInspection)}"));
32-
#endif
3338
}
3439

3540
_supportedInspections = inspections.ToHashSet();
3641
}
3742

43+
// ReSharper disable once RedundantAssignment : conditional must be void but we can use ref
44+
[Conditional("DEBUG")]
45+
private static void MustThrowException(ref bool dieNow)
46+
{
47+
dieNow = true;
48+
}
49+
3850
public void RemoveInspections(params Type[] inspections)
3951
{
4052
_supportedInspections = _supportedInspections.Except(inspections).ToHashSet();

Rubberduck.CodeAnalysis/Inspections/Concrete/ArgumentWithIncompatibleObjectTypeInspection.cs

Lines changed: 4 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
2121
/// <why>
2222
/// The VBA compiler does not check whether different object types are compatible. Instead there is a runtime error whenever the types are incompatible.
2323
/// </why>
24-
/// <example hasResult="true">
24+
/// <example hasresult="true">
2525
/// <![CDATA[
2626
/// IInterface:
2727
///
@@ -49,7 +49,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
4949
/// End Sub
5050
/// ]]>
5151
/// </example>
52-
/// <example hasResult="false">
52+
/// <example hasresult="false">
5353
/// <![CDATA[
5454
/// IInterface:
5555
///
@@ -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),

0 commit comments

Comments
 (0)