Skip to content

Commit efc2b99

Browse files
committed
Add support for adding/removing inspections from a quick fix dynamically. More C# 7 stuff; clean up the inspection tests
1 parent 4bfe08e commit efc2b99

File tree

102 files changed

+1058
-1764
lines changed

Some content is hidden

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

102 files changed

+1058
-1764
lines changed

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@
2929
<NoWarn>1591</NoWarn>
3030
<PlatformTarget>AnyCPU</PlatformTarget>
3131
<UseVSHostingProcess>true</UseVSHostingProcess>
32+
<LangVersion>7.1</LangVersion>
3233
</PropertyGroup>
3334
<PropertyGroup Condition=" '$(Configuration)|$(Platform)' == 'Release|AnyCPU' ">
3435
<DebugType>full</DebugType>
@@ -41,6 +42,7 @@
4142
<DocumentationFile>bin\Release\Rubberduck.XML</DocumentationFile>
4243
<DebugSymbols>true</DebugSymbols>
4344
<NoWarn>1591</NoWarn>
45+
<LangVersion>7.1</LangVersion>
4446
</PropertyGroup>
4547
<PropertyGroup Condition="'$(Configuration)|$(Platform)' == 'DebugAccess|AnyCPU'">
4648
<DebugSymbols>true</DebugSymbols>
@@ -54,6 +56,7 @@
5456
<CodeAnalysisRuleSet>MinimumRecommendedRules.ruleset</CodeAnalysisRuleSet>
5557
<WarningLevel>4</WarningLevel>
5658
<Optimize>false</Optimize>
59+
<LangVersion>7.1</LangVersion>
5760
</PropertyGroup>
5861
<PropertyGroup Condition="'$(Configuration)|$(Platform)' == 'Debug|x64'">
5962
<DebugSymbols>true</DebugSymbols>
@@ -151,6 +154,7 @@
151154
<CodeAnalysisRuleSet>MinimumRecommendedRules.ruleset</CodeAnalysisRuleSet>
152155
<WarningLevel>4</WarningLevel>
153156
<Optimize>false</Optimize>
157+
<LangVersion>7.1</LangVersion>
154158
</PropertyGroup>
155159
<PropertyGroup Condition="'$(Configuration)|$(Platform)' == 'Debug64|x64'">
156160
<DebugSymbols>true</DebugSymbols>
@@ -191,6 +195,7 @@
191195
<ErrorReport>prompt</ErrorReport>
192196
<CodeAnalysisRuleSet>MinimumRecommendedRules.ruleset</CodeAnalysisRuleSet>
193197
<WarningLevel>4</WarningLevel>
198+
<LangVersion>7.1</LangVersion>
194199
</PropertyGroup>
195200
<PropertyGroup Condition="'$(Configuration)|$(Platform)' == 'Release64|x64'">
196201
<DebugSymbols>true</DebugSymbols>
Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,24 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using Rubberduck.Parsing.Inspections.Abstract;
5+
using Rubberduck.Parsing.VBA;
6+
7+
namespace Rubberduck.Inspections.Abstract
8+
{
9+
public class QuickFixBase
10+
{
11+
private HashSet<Type> _supportedInspections = new HashSet<Type>();
12+
public IReadOnlyCollection<Type> SupportedInspections => _supportedInspections.ToList();
13+
14+
public void RemoveInspections(params IInspection[] inspections)
15+
{
16+
_supportedInspections = _supportedInspections.Except(inspections.Select(s => s.Type)).ToHashSet();
17+
}
18+
19+
public void RegisterInspections(params IInspection[] inspections)
20+
{
21+
_supportedInspections = inspections.Where(w => w != null).Select(s => s.Type).ToHashSet();
22+
}
23+
}
24+
}
Lines changed: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,21 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Parsing.Inspections.Abstract;
4+
5+
namespace Rubberduck.Inspections
6+
{
7+
public class InspectionLocator
8+
{
9+
private readonly IEnumerable<IInspection> _inspections;
10+
11+
public InspectionLocator(IEnumerable<IInspection> inspections)
12+
{
13+
_inspections = inspections;
14+
}
15+
16+
public IInspection GetInspection<T>() where T: IInspection
17+
{
18+
return _inspections.FirstOrDefault(s => s.Type == typeof(T));
19+
}
20+
}
21+
}

Rubberduck.Inspections/QuickFixes/AddIdentifierToWhiteListQuickFix.cs

Lines changed: 5 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
1-
using System;
2-
using System.Collections.Generic;
31
using System.Linq;
2+
using Rubberduck.Inspections.Abstract;
43
using Rubberduck.Inspections.Concrete;
54
using Rubberduck.Parsing.Inspections.Abstract;
65
using Rubberduck.Parsing.Inspections.Resources;
@@ -9,22 +8,17 @@
98

109
namespace Rubberduck.Inspections.QuickFixes
1110
{
12-
public sealed class AddIdentifierToWhiteListQuickFix : IQuickFix
11+
public sealed class AddIdentifierToWhiteListQuickFix : QuickFixBase, IQuickFix
1312
{
1413
private readonly IPersistanceService<CodeInspectionSettings> _settings;
15-
private static readonly HashSet<Type> _supportedInspections = new HashSet<Type>
16-
{
17-
typeof(HungarianNotationInspection),
18-
typeof(UseMeaningfulNameInspection)
19-
};
2014

21-
public AddIdentifierToWhiteListQuickFix(IPersistanceService<CodeInspectionSettings> settings)
15+
public AddIdentifierToWhiteListQuickFix(IPersistanceService<CodeInspectionSettings> settings, InspectionLocator inspectionLocator)
2216
{
2317
_settings = settings;
18+
RegisterInspections(inspectionLocator.GetInspection<HungarianNotationInspection>(),
19+
inspectionLocator.GetInspection<UseMeaningfulNameInspection>());
2420
}
2521

26-
public IReadOnlyCollection<Type> SupportedInspections => _supportedInspections.ToList();
27-
2822
public void Fix(IInspectionResult result)
2923
{
3024
var inspectionSettings = _settings.Load(new CodeInspectionSettings()) ?? new CodeInspectionSettings();

Rubberduck.Inspections/QuickFixes/ApplicationWorksheetFunctionQuickFix.cs

Lines changed: 4 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,24 +1,20 @@
1-
using System;
2-
using System.Collections.Generic;
3-
using System.Linq;
1+
using Rubberduck.Inspections.Abstract;
42
using Rubberduck.Inspections.Concrete;
53
using Rubberduck.Parsing.Inspections.Abstract;
64
using Rubberduck.Parsing.Inspections.Resources;
75
using Rubberduck.Parsing.VBA;
86

97
namespace Rubberduck.Inspections.QuickFixes
108
{
11-
public sealed class ApplicationWorksheetFunctionQuickFix : IQuickFix
9+
public sealed class ApplicationWorksheetFunctionQuickFix : QuickFixBase, IQuickFix
1210
{
1311
private readonly RubberduckParserState _state;
14-
private static readonly HashSet<Type> _supportedInspections = new HashSet<Type> {typeof(ApplicationWorksheetFunctionInspection) };
1512

16-
public ApplicationWorksheetFunctionQuickFix(RubberduckParserState state)
13+
public ApplicationWorksheetFunctionQuickFix(RubberduckParserState state, InspectionLocator inspectionLocator)
1714
{
1815
_state = state;
16+
RegisterInspections(inspectionLocator.GetInspection<ApplicationWorksheetFunctionInspection>());
1917
}
20-
21-
public IReadOnlyCollection<Type> SupportedInspections => _supportedInspections.ToList();
2218

2319
public void Fix(IInspectionResult result)
2420
{

Rubberduck.Inspections/QuickFixes/AssignedByValParameterMakeLocalCopyQuickFix.cs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
using System.Collections.Generic;
88
using System.Windows.Forms;
99
using Antlr4.Runtime;
10+
using Rubberduck.Inspections.Abstract;
1011
using Rubberduck.Inspections.Concrete;
1112
using Rubberduck.Parsing.Inspections.Abstract;
1213
using Rubberduck.Parsing.Inspections.Resources;
@@ -15,20 +16,18 @@
1516

1617
namespace Rubberduck.Inspections.QuickFixes
1718
{
18-
public sealed class AssignedByValParameterMakeLocalCopyQuickFix : IQuickFix
19+
public sealed class AssignedByValParameterMakeLocalCopyQuickFix : QuickFixBase, IQuickFix
1920
{
2021
private readonly IAssignedByValParameterQuickFixDialogFactory _dialogFactory;
2122
private readonly RubberduckParserState _parserState;
22-
private static readonly HashSet<Type> _supportedInspections = new HashSet<Type> { typeof(AssignedByValParameterInspection) };
2323

24-
public AssignedByValParameterMakeLocalCopyQuickFix(RubberduckParserState parserState, IAssignedByValParameterQuickFixDialogFactory dialogFactory)
24+
public AssignedByValParameterMakeLocalCopyQuickFix(RubberduckParserState state, InspectionLocator inspectionLocator, IAssignedByValParameterQuickFixDialogFactory dialogFactory)
2525
{
2626
_dialogFactory = dialogFactory;
27-
_parserState = parserState;
27+
_parserState = state;
28+
RegisterInspections(inspectionLocator.GetInspection<AssignedByValParameterInspection>());
2829
}
2930

30-
public IReadOnlyCollection<Type> SupportedInspections => _supportedInspections.ToList();
31-
3231
public void Fix(IInspectionResult result)
3332
{
3433
var forbiddenNames = _parserState.DeclarationFinder.GetDeclarationsWithIdentifiersToAvoid(result.Target).Select(n => n.IdentifierName);

Rubberduck.Inspections/QuickFixes/ChangeDimToPrivateQuickFix.cs

Lines changed: 4 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,4 @@
1-
using System;
2-
using System.Collections.Generic;
3-
using System.Linq;
1+
using Rubberduck.Inspections.Abstract;
42
using Rubberduck.Inspections.Concrete;
53
using Rubberduck.Parsing.Grammar;
64
using Rubberduck.Parsing.Inspections.Abstract;
@@ -9,18 +7,16 @@
97

108
namespace Rubberduck.Inspections.QuickFixes
119
{
12-
public sealed class ChangeDimToPrivateQuickFix : IQuickFix
10+
public sealed class ChangeDimToPrivateQuickFix : QuickFixBase, IQuickFix
1311
{
14-
private static readonly HashSet<Type> _supportedInspections = new HashSet<Type> { typeof(ModuleScopeDimKeywordInspection) };
1512
private readonly RubberduckParserState _state;
1613

17-
public ChangeDimToPrivateQuickFix(RubberduckParserState state)
14+
public ChangeDimToPrivateQuickFix(RubberduckParserState state, InspectionLocator inspectionLocator)
1815
{
1916
_state = state;
17+
RegisterInspections(inspectionLocator.GetInspection<ModuleScopeDimKeywordInspection>());
2018
}
2119

22-
public IReadOnlyCollection<Type> SupportedInspections => _supportedInspections.ToList();
23-
2420
public void Fix(IInspectionResult result)
2521
{
2622
var rewriter = _state.GetRewriter(result.QualifiedSelection.QualifiedName);

Rubberduck.Inspections/QuickFixes/ChangeIntegerToLongQuickFix.cs

Lines changed: 4 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,9 @@
11
using System;
22
using Rubberduck.Parsing.Grammar;
3-
using System.Collections.Generic;
43
using System.Linq;
54
using Antlr4.Runtime;
65
using Rubberduck.Common;
6+
using Rubberduck.Inspections.Abstract;
77
using Rubberduck.Inspections.Concrete;
88
using Rubberduck.Parsing.Inspections.Abstract;
99
using Rubberduck.Parsing.Inspections.Resources;
@@ -13,22 +13,16 @@
1313

1414
namespace Rubberduck.Inspections.QuickFixes
1515
{
16-
public class ChangeIntegerToLongQuickFix : IQuickFix
16+
public class ChangeIntegerToLongQuickFix : QuickFixBase, IQuickFix
1717
{
1818
private readonly RubberduckParserState _state;
1919

20-
private static readonly HashSet<Type> _supportedInspections = new HashSet<Type>
21-
{
22-
typeof(IntegerDataTypeInspection)
23-
};
24-
25-
public ChangeIntegerToLongQuickFix(RubberduckParserState state)
20+
public ChangeIntegerToLongQuickFix(RubberduckParserState state, InspectionLocator inspectionLocator)
2621
{
2722
_state = state;
23+
RegisterInspections(inspectionLocator.GetInspection<IntegerDataTypeInspection>());
2824
}
2925

30-
public IReadOnlyCollection<Type> SupportedInspections { get; } = _supportedInspections.ToList();
31-
3226
public void Fix(IInspectionResult result)
3327
{
3428
var rewriter = _state.GetRewriter(result.Target);

Rubberduck.Inspections/QuickFixes/ChangeProcedureToFunctionQuickFix.cs

Lines changed: 4 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
using System;
2-
using System.Collections.Generic;
32
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
44
using Rubberduck.Inspections.Concrete;
55
using Rubberduck.Parsing.Grammar;
66
using Rubberduck.Parsing.Inspections.Abstract;
@@ -10,17 +10,14 @@
1010

1111
namespace Rubberduck.Inspections.QuickFixes
1212
{
13-
public sealed class ChangeProcedureToFunctionQuickFix : IQuickFix
13+
public sealed class ChangeProcedureToFunctionQuickFix : QuickFixBase, IQuickFix
1414
{
15-
private static readonly HashSet<Type> _supportedInspections = new HashSet<Type> { typeof(ProcedureCanBeWrittenAsFunctionInspection) };
16-
17-
public IReadOnlyCollection<Type> SupportedInspections => _supportedInspections.ToList();
18-
1915
private readonly RubberduckParserState _state;
2016

21-
public ChangeProcedureToFunctionQuickFix(RubberduckParserState state)
17+
public ChangeProcedureToFunctionQuickFix(RubberduckParserState state, InspectionLocator inspectionLocator)
2218
{
2319
_state = state;
20+
RegisterInspections(inspectionLocator.GetInspection<ProcedureCanBeWrittenAsFunctionInspection>());
2421
}
2522

2623
public void Fix(IInspectionResult result)

Rubberduck.Inspections/QuickFixes/ConvertToProcedureQuickFix.cs

Lines changed: 12 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
1-
using System;
21
using System.Collections.Generic;
32
using System.Linq;
43
using Antlr4.Runtime;
4+
using Rubberduck.Inspections.Abstract;
55
using Rubberduck.Inspections.Concrete;
66
using Rubberduck.Parsing.Grammar;
77
using Rubberduck.Parsing.Inspections.Abstract;
@@ -11,34 +11,27 @@
1111

1212
namespace Rubberduck.Inspections.QuickFixes
1313
{
14-
public sealed class ConvertToProcedureQuickFix : IQuickFix
14+
public sealed class ConvertToProcedureQuickFix : QuickFixBase, IQuickFix
1515
{
1616
private readonly RubberduckParserState _state;
17-
private static readonly HashSet<Type> _supportedInspections = new HashSet<Type>
18-
{
19-
typeof(NonReturningFunctionInspection),
20-
typeof(FunctionReturnValueNotUsedInspection)
21-
};
2217

23-
public ConvertToProcedureQuickFix(RubberduckParserState state)
18+
public ConvertToProcedureQuickFix(RubberduckParserState state, InspectionLocator inspectionLocator)
2419
{
2520
_state = state;
21+
RegisterInspections(inspectionLocator.GetInspection<NonReturningFunctionInspection>(),
22+
inspectionLocator.GetInspection<FunctionReturnValueNotUsedInspection>());
2623
}
2724

28-
public IReadOnlyCollection<Type> SupportedInspections => _supportedInspections.ToList();
29-
3025
public void Fix(IInspectionResult result)
3126
{
32-
var functionContext = result.Context as VBAParser.FunctionStmtContext;
33-
if (functionContext != null)
34-
{
35-
ConvertFunction(result, functionContext);
36-
}
37-
38-
var propertyGetContext = result.Context as VBAParser.PropertyGetStmtContext;
39-
if (propertyGetContext != null)
27+
switch (result.Context)
4028
{
41-
ConvertPropertyGet(result, propertyGetContext);
29+
case VBAParser.FunctionStmtContext functionContext:
30+
ConvertFunction(result, functionContext);
31+
break;
32+
case VBAParser.PropertyGetStmtContext propertyGetContext:
33+
ConvertPropertyGet(result, propertyGetContext);
34+
break;
4235
}
4336
}
4437

0 commit comments

Comments
 (0)