Skip to content

Commit dfaa590

Browse files
authored
Merge pull request #3435 from Vogel612/typecrutch
Removes IInspection interceptors, mechanics replaced with templated method.
2 parents 2770646 + 1d78020 commit dfaa590

File tree

71 files changed

+92
-334
lines changed

Some content is hidden

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

71 files changed

+92
-334
lines changed

RetailCoder.VBE/Root/EnumerableCounterInterceptor.cs

Lines changed: 0 additions & 34 deletions
This file was deleted.

RetailCoder.VBE/Root/InterceptedException.cs

Lines changed: 0 additions & 13 deletions
This file was deleted.

RetailCoder.VBE/Root/InterceptorBase.cs

Lines changed: 0 additions & 36 deletions
This file was deleted.

RetailCoder.VBE/Root/RubberduckModule.cs

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -294,8 +294,12 @@ private void ApplyAbstractFactoryConvention(IEnumerable<Assembly> assemblies)
294294
private void BindCodeInspectionTypes(IEnumerable<Assembly> assemblies)
295295
{
296296
var inspections = assemblies
297-
.SelectMany(a => a.GetTypes().Where(type => type.IsClass && !type.IsAbstract && type.GetInterfaces().Contains(typeof(IInspection))))
298-
.ToList();
297+
.SelectMany(a => a.GetTypes()
298+
.Where(type => type.IsClass
299+
&& !type.IsAbstract
300+
&& type.GetInterfaces().Contains(typeof(IInspection))
301+
)
302+
);
299303

300304
// multibinding for IEnumerable<IInspection> dependency
301305
foreach(var inspection in inspections)
@@ -308,17 +312,12 @@ private void BindCodeInspectionTypes(IEnumerable<Assembly> assemblies)
308312
.InCallScope()
309313
.Named(inspection.FullName);
310314

311-
binding.Intercept().With<TimedCallLoggerInterceptor>();
312-
binding.Intercept().With<EnumerableCounterInterceptor<IInspectionResult>>();
313-
314315
var localInspection = inspection;
315316
Bind<IInspection>().ToMethod(c => (IInspection)c.Kernel.Get(iParseTreeInspection, localInspection.FullName));
316317
}
317318
else
318319
{
319320
var binding = Bind<IInspection>().To(inspection).InCallScope();
320-
binding.Intercept().With<TimedCallLoggerInterceptor>();
321-
binding.Intercept().With<EnumerableCounterInterceptor<IInspectionResult>>();
322321
}
323322
}
324323
}

RetailCoder.VBE/Root/TimedCallLoggerInterceptor.cs

Lines changed: 0 additions & 41 deletions
This file was deleted.

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -373,10 +373,6 @@
373373
<Compile Include="Refactorings\ExtractMethod\IExtractMethodProc.cs" />
374374
<Compile Include="Refactorings\ExtractMethod\IExtractMethodRule.cs" />
375375
<Compile Include="Refactorings\ExtractMethod\IExtractMethodSelectionValidation.cs" />
376-
<Compile Include="Root\EnumerableCounterInterceptor.cs" />
377-
<Compile Include="Root\InterceptedException.cs" />
378-
<Compile Include="Root\InterceptorBase.cs" />
379-
<Compile Include="Root\TimedCallLoggerInterceptor.cs" />
380376
<Compile Include="RubberduckGuid.cs" />
381377
<Compile Include="RubberduckProgId.cs" />
382378
<Compile Include="Settings\CodeInspectionConfigProvider.cs" />

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 & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -18,11 +18,9 @@ public class ApplicationWorksheetFunctionInspection : InspectionBase
1818
public ApplicationWorksheetFunctionInspection(RubberduckParserState state)
1919
: base(state, CodeInspectionSeverity.Suggestion) { }
2020

21-
public override Type Type => typeof(ApplicationWorksheetFunctionInspection);
22-
2321
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
2422

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

Rubberduck.Inspections/Concrete/AssignedByValParameterInspection.cs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -15,12 +15,10 @@ public sealed class AssignedByValParameterInspection : InspectionBase
1515
public AssignedByValParameterInspection(RubberduckParserState state)
1616
: base(state)
1717
{ }
18-
19-
public override Type Type => typeof(AssignedByValParameterInspection);
20-
18+
2119
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
2220

23-
public override IEnumerable<IInspectionResult> GetInspectionResults()
21+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2422
{
2523
var parameters = State.DeclarationFinder.UserDeclarations(DeclarationType.Parameter)
2624
.Cast<ParameterDeclaration>()

Rubberduck.Inspections/Concrete/ConstantNotUsedInspection.cs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -18,11 +18,9 @@ public sealed class ConstantNotUsedInspection : InspectionBase
1818
public ConstantNotUsedInspection(RubberduckParserState state)
1919
: base(state) { }
2020

21-
public override Type Type => typeof(ConstantNotUsedInspection);
22-
2321
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
2422

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

0 commit comments

Comments
 (0)