Skip to content

Commit 54f0c3f

Browse files
committed
Removed InspectionType default value from inspection classes
1 parent 3963c7a commit 54f0c3f

File tree

66 files changed

+10
-133
lines changed

Some content is hidden

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

66 files changed

+10
-133
lines changed

Rubberduck.Inspections/Abstract/InspectionBase.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,6 @@ public abstract class InspectionBase : IInspection
2222
protected InspectionBase(RubberduckParserState state)
2323
{
2424
State = state;
25-
Severity = CodeInspectionSeverity.Warning;
2625
Name = GetType().Name;
2726
}
2827

@@ -34,7 +33,7 @@ protected InspectionBase(RubberduckParserState state)
3433
/// <summary>
3534
/// Gets the type of inspection; used for regrouping inspections.
3635
/// </summary>
37-
public abstract CodeInspectionType InspectionType { get; }
36+
public CodeInspectionType InspectionType { get; set; } = CodeInspectionType.CodeQualityIssues;
3837

3938
/// <summary>
4039
/// The inspection type name, obtained by reflection.
@@ -44,7 +43,7 @@ protected InspectionBase(RubberduckParserState state)
4443
/// <summary>
4544
/// Inspection severity level. Can control whether an inspection is enabled.
4645
/// </summary>
47-
public CodeInspectionSeverity Severity { get; set; }
46+
public CodeInspectionSeverity Severity { get; set; } = CodeInspectionSeverity.Warning;
4847

4948
/// <summary>
5049
/// Meta-information about why an inspection exists.

Rubberduck.Inspections/Abstract/ParseTreeInspectionBase.cs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
using Rubberduck.Parsing.Inspections.Abstract;
2-
using Rubberduck.Parsing.Inspections.Resources;
32
using Rubberduck.Parsing.VBA;
43

54
namespace Rubberduck.Inspections.Abstract
@@ -9,7 +8,6 @@ public abstract class ParseTreeInspectionBase : InspectionBase, IParseTreeInspec
98
protected ParseTreeInspectionBase(RubberduckParserState state)
109
: base(state) { }
1110

12-
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
1311
public abstract IInspectionListener Listener { get; }
1412
public virtual ParsePass Pass => ParsePass.CodePanePass;
1513
}

Rubberduck.Inspections/Concrete/ApplicationWorksheetFunctionInspection.cs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,6 @@ public class ApplicationWorksheetFunctionInspection : InspectionBase
1717
public ApplicationWorksheetFunctionInspection(RubberduckParserState state)
1818
: base(state) { }
1919

20-
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
21-
2220
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2321
{
2422
var excel = State.DeclarationFinder.Projects.SingleOrDefault(item => !item.IsUserDefined && item.IdentifierName == "Excel");

Rubberduck.Inspections/Concrete/AssignedByValParameterInspection.cs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,8 +15,6 @@ public AssignedByValParameterInspection(RubberduckParserState state)
1515
: base(state)
1616
{ }
1717

18-
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
19-
2018
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2119
{
2220
var parameters = State.DeclarationFinder.UserDeclarations(DeclarationType.Parameter)

Rubberduck.Inspections/Concrete/BooleanAssignedInIfElseInspection.cs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@
77
using Rubberduck.Parsing.Grammar;
88
using Rubberduck.Parsing.Inspections.Abstract;
99
using Rubberduck.Parsing.Inspections.Resources;
10-
using Rubberduck.Parsing.Symbols;
1110
using Rubberduck.Parsing.VBA;
1211
using Rubberduck.VBEditor;
1312

@@ -18,8 +17,6 @@ public sealed class BooleanAssignedInIfElseInspection : ParseTreeInspectionBase
1817
public BooleanAssignedInIfElseInspection(RubberduckParserState state)
1918
: base(state) { }
2019

21-
public override CodeInspectionType InspectionType => CodeInspectionType.MaintainabilityAndReadabilityIssues;
22-
2320
public override IInspectionListener Listener { get; } =
2421
new BooleanAssignedInIfElseListener();
2522

Rubberduck.Inspections/Concrete/ConstantNotUsedInspection.cs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,6 @@ public sealed class ConstantNotUsedInspection : InspectionBase
1717
public ConstantNotUsedInspection(RubberduckParserState state)
1818
: base(state) { }
1919

20-
public override CodeInspectionType InspectionType => CodeInspectionType.CodeQualityIssues;
21-
2220
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2321
{
2422
var results = State.DeclarationFinder.UserDeclarations(DeclarationType.Constant)

Rubberduck.Inspections/Concrete/DefTypeStatementInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -20,8 +20,7 @@ public DefTypeStatementInspection(RubberduckParserState state)
2020
{
2121
Listener = new DefTypeStatementInspectionListener();
2222
}
23-
24-
public override CodeInspectionType InspectionType => CodeInspectionType.LanguageOpportunities;
23+
2524
public override IInspectionListener Listener { get; }
2625

2726
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()

Rubberduck.Inspections/Concrete/DefaultProjectNameInspection.cs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
using Rubberduck.Inspections.Results;
55
using Rubberduck.Parsing.Inspections;
66
using Rubberduck.Parsing.Inspections.Abstract;
7-
using Rubberduck.Parsing.Inspections.Resources;
87
using Rubberduck.Parsing.Symbols;
98
using Rubberduck.Parsing.VBA;
109

@@ -16,8 +15,6 @@ public sealed class DefaultProjectNameInspection : InspectionBase
1615
public DefaultProjectNameInspection(RubberduckParserState state)
1716
: base(state) { }
1817

19-
public override CodeInspectionType InspectionType => CodeInspectionType.MaintainabilityAndReadabilityIssues;
20-
2118
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2219
{
2320
var projects = State.DeclarationFinder.UserDeclarations(DeclarationType.Project)

Rubberduck.Inspections/Concrete/EmptyCaseBlockInspection.cs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -20,8 +20,6 @@ public EmptyCaseBlockInspection(RubberduckParserState state)
2020
public override IInspectionListener Listener { get; } =
2121
new EmptyCaseBlockListener();
2222

23-
public override CodeInspectionType InspectionType => CodeInspectionType.MaintainabilityAndReadabilityIssues;
24-
2523
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2624
{
2725
return Listener.Contexts

Rubberduck.Inspections/Concrete/EmptyDoWhileBlockInspection.cs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,6 @@ internal class EmptyDoWhileBlockInspection : ParseTreeInspectionBase
1717
public EmptyDoWhileBlockInspection(RubberduckParserState state)
1818
: base(state) { }
1919

20-
public override CodeInspectionType InspectionType => CodeInspectionType.MaintainabilityAndReadabilityIssues;
21-
2220
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2321
{
2422
return Listener.Contexts

0 commit comments

Comments
 (0)