Skip to content

Commit 286f4fd

Browse files
committed
Replace Interceptor implementations with abstract class implementation
1 parent 2770646 commit 286f4fd

File tree

63 files changed

+84
-77
lines changed

Some content is hidden

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

63 files changed

+84
-77
lines changed

Rubberduck.Inspections/Abstract/InspectionBase.cs

Lines changed: 20 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -8,12 +8,16 @@
88
using Rubberduck.Parsing.Symbols;
99
using Rubberduck.Parsing.VBA;
1010
using Rubberduck.VBEditor;
11+
using System.Diagnostics;
12+
using NLog;
1113

1214
namespace Rubberduck.Inspections.Abstract
1315
{
1416
public abstract class InspectionBase : IInspection
1517
{
1618
protected readonly RubberduckParserState State;
19+
20+
private readonly ILogger _logger = LogManager.GetCurrentClassLogger();
1721
private readonly CodeInspectionSeverity _defaultSeverity;
1822

1923
protected InspectionBase(RubberduckParserState state, CodeInspectionSeverity defaultSeverity = CodeInspectionSeverity.Warning)
@@ -24,11 +28,6 @@ protected InspectionBase(RubberduckParserState state, CodeInspectionSeverity def
2428
Name = GetType().Name;
2529
}
2630

27-
/// <summary>
28-
/// Gets the type of the inspection class. GetType() returns an interceptor proxy type.
29-
/// </summary>
30-
public abstract Type Type { get; }
31-
3231
/// <summary>
3332
/// Gets a value the severity level to reset to, the "factory default" setting.
3433
/// </summary>
@@ -44,12 +43,6 @@ protected InspectionBase(RubberduckParserState state, CodeInspectionSeverity def
4443
/// </summary>
4544
public abstract CodeInspectionType InspectionType { get; }
4645

47-
/// <summary>
48-
/// A method that inspects the parser state and returns all issues it can find.
49-
/// </summary>
50-
/// <returns></returns>
51-
public abstract IEnumerable<IInspectionResult> GetInspectionResults();
52-
5346
/// <summary>
5447
/// The inspection type name, obtained by reflection.
5548
/// </summary>
@@ -166,5 +159,21 @@ public int CompareTo(object obj)
166159
{
167160
return CompareTo(obj as IInspection);
168161
}
162+
protected abstract IEnumerable<IInspectionResult> DoGetInspectionResults();
163+
164+
/// <summary>
165+
/// A method that inspects the parser state and returns all issues it can find.
166+
/// </summary>
167+
/// <returns></returns>
168+
public IEnumerable<IInspectionResult> GetInspectionResults()
169+
{
170+
var _stopwatch = new Stopwatch();
171+
_stopwatch.Start();
172+
var result = DoGetInspectionResults();
173+
_stopwatch.Stop();
174+
_logger.Trace("Intercepted invocation of '{0}.{1}' returned {2} objects.", GetType().Name, nameof(DoGetInspectionResults), result.Count());
175+
_logger.Trace("Intercepted invocation of '{0}.{1}' ran for {2}ms", GetType().Name, nameof(DoGetInspectionResults), _stopwatch.ElapsedMilliseconds);
176+
return result;
177+
}
169178
}
170179
}

Rubberduck.Inspections/Concrete/ApplicationWorksheetFunctionInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ public ApplicationWorksheetFunctionInspection(RubberduckParserState state)
2222

2323
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
2424

25-
public override IEnumerable<IInspectionResult> GetInspectionResults()
25+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2626
{
2727
var excel = State.DeclarationFinder.Projects.SingleOrDefault(item => !item.IsUserDefined && item.IdentifierName == "Excel");
2828
if (excel == null) { return Enumerable.Empty<IInspectionResult>(); }

Rubberduck.Inspections/Concrete/AssignedByValParameterInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ public AssignedByValParameterInspection(RubberduckParserState state)
2020

2121
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
2222

23-
public override IEnumerable<IInspectionResult> GetInspectionResults()
23+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2424
{
2525
var parameters = State.DeclarationFinder.UserDeclarations(DeclarationType.Parameter)
2626
.Cast<ParameterDeclaration>()

Rubberduck.Inspections/Concrete/ConstantNotUsedInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ public ConstantNotUsedInspection(RubberduckParserState state)
2222

2323
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
2424

25-
public override IEnumerable<IInspectionResult> GetInspectionResults()
25+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2626
{
2727
var results = State.DeclarationFinder.UserDeclarations(DeclarationType.Constant)
2828
.Where(declaration => declaration.Context != null

Rubberduck.Inspections/Concrete/DefaultProjectNameInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ public DefaultProjectNameInspection(RubberduckParserState state)
2121

2222
public override CodeInspectionType InspectionType => CodeInspectionType.MaintainabilityAndReadabilityIssues;
2323

24-
public override IEnumerable<IInspectionResult> GetInspectionResults()
24+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2525
{
2626
var projects = State.DeclarationFinder.UserDeclarations(DeclarationType.Project)
2727
.Where(item => item.IdentifierName.StartsWith("VBAProject"))

Rubberduck.Inspections/Concrete/EmptyCaseBlockInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ public EmptyCaseBlockInspection(RubberduckParserState state)
2323

2424
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
2525

26-
public override IEnumerable<IInspectionResult> GetInspectionResults()
26+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2727
{
2828
return Listener.Contexts
2929
.Where(result => !IsIgnoringInspectionResultFor(result.ModuleName, result.Context.Start.Line))

Rubberduck.Inspections/Concrete/EmptyDoWhileBlockInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ public EmptyDoWhileBlockInspection(RubberduckParserState state)
2020

2121
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
2222

23-
public override IEnumerable<IInspectionResult> GetInspectionResults()
23+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2424
{
2525
return Listener.Contexts
2626
.Where(result => !IsIgnoringInspectionResultFor(result.ModuleName, result.Context.Start.Line))

Rubberduck.Inspections/Concrete/EmptyElseBlockInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ public EmptyElseBlockInspection(RubberduckParserState state)
2020

2121
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
2222

23-
public override IEnumerable<IInspectionResult> GetInspectionResults()
23+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2424
{
2525
return Listener.Contexts
2626
.Where(result => !IsIgnoringInspectionResultFor(result.ModuleName, result.Context.Start.Line))

Rubberduck.Inspections/Concrete/EmptyForEachBlockInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ public EmptyForEachBlockInspection(RubberduckParserState state)
2020

2121
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
2222

23-
public override IEnumerable<IInspectionResult> GetInspectionResults()
23+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2424
{
2525
return Listener.Contexts
2626
.Where(result => !IsIgnoringInspectionResultFor(result.ModuleName, result.Context.Start.Line))

Rubberduck.Inspections/Concrete/EmptyForLoopBlockInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ public EmptyForLoopBlockInspection(RubberduckParserState state)
2020

2121
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
2222

23-
public override IEnumerable<IInspectionResult> GetInspectionResults()
23+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2424
{
2525
return Listener.Contexts
2626
.Where(result => !IsIgnoringInspectionResultFor(result.ModuleName, result.Context.Start.Line))

0 commit comments

Comments
 (0)