Skip to content

Commit dabff17

Browse files
authored
Merge branch 'next' into next
2 parents 58a29dd + 3a210be commit dabff17

16 files changed

+2281
-1851
lines changed
Lines changed: 94 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,94 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using Rubberduck.Inspections.Abstract;
5+
using Rubberduck.Parsing.Inspections.Abstract;
6+
using Rubberduck.Parsing.Inspections.Resources;
7+
using Antlr4.Runtime;
8+
using Antlr4.Runtime.Misc;
9+
using Rubberduck.Parsing.Grammar;
10+
using Rubberduck.Parsing;
11+
using Rubberduck.Parsing.VBA;
12+
using Rubberduck.Inspections.Results;
13+
14+
namespace Rubberduck.Inspections.Concrete
15+
{
16+
[Flags]
17+
public enum ConditionBlockToInspect
18+
{
19+
NA = 0x0,
20+
If = 0x1,
21+
ElseIf = 0x2,
22+
Else = 0x4,
23+
All = If | ElseIf | Else
24+
}
25+
26+
internal class EmptyConditionBlockInspection : ParseTreeInspectionBase
27+
{
28+
public EmptyConditionBlockInspection(RubberduckParserState state,
29+
ConditionBlockToInspect BlockToInspect)
30+
: base(state, CodeInspectionSeverity.Suggestion)
31+
{
32+
_blockToInspect = BlockToInspect;
33+
_listener = new EmptyConditionBlockListener(BlockToInspect);
34+
}
35+
36+
public static ConditionBlockToInspect _blockToInspect { get; private set; }
37+
38+
public override Type Type => typeof(EmptyConditionBlockInspection);
39+
40+
public override IEnumerable<IInspectionResult> GetInspectionResults()
41+
{
42+
return Listener.Contexts
43+
.Where(result => !IsIgnoringInspectionResultFor(result.ModuleName, result.Context.Start.Line))
44+
.Select(result => new QualifiedContextInspectionResult(this,
45+
InspectionsUI.EmptyConditionBlockInspectionsResultFormat,
46+
result));
47+
}
48+
49+
private IInspectionListener _listener;
50+
public override IInspectionListener Listener { get { return _listener; } }
51+
52+
public class EmptyConditionBlockListener : EmptyBlockInspectionListenerBase
53+
{
54+
ConditionBlockToInspect _blockToInspect;
55+
56+
public EmptyConditionBlockListener(ConditionBlockToInspect blockToInspect)
57+
{
58+
_blockToInspect = blockToInspect;
59+
}
60+
61+
public override void EnterIfStmt([NotNull] VBAParser.IfStmtContext context)
62+
{
63+
if (_blockToInspect.HasFlag(ConditionBlockToInspect.If))
64+
{
65+
InspectBlockForExecutableStatements(context.block(), context);
66+
}
67+
}
68+
69+
public override void EnterElseIfBlock([NotNull] VBAParser.ElseIfBlockContext context)
70+
{
71+
if (_blockToInspect.HasFlag(ConditionBlockToInspect.ElseIf))
72+
{
73+
InspectBlockForExecutableStatements(context.block(), context);
74+
}
75+
}
76+
77+
public override void EnterSingleLineIfStmt([NotNull] VBAParser.SingleLineIfStmtContext context)
78+
{
79+
if (context.ifWithEmptyThen() != null & _blockToInspect.HasFlag(ConditionBlockToInspect.If))
80+
{
81+
AddResult(new QualifiedContext<ParserRuleContext>(CurrentModuleName, context.ifWithEmptyThen()));
82+
}
83+
}
84+
85+
public override void EnterElseBlock([NotNull] VBAParser.ElseBlockContext context)
86+
{
87+
if (_blockToInspect.HasFlag(ConditionBlockToInspect.Else))
88+
{
89+
InspectBlockForExecutableStatements(context.block(), context);
90+
}
91+
}
92+
}
93+
}
94+
}

Rubberduck.Inspections/Concrete/EmptyElseBlockInspection.cs

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

Rubberduck.Inspections/Concrete/EmptyIfBlockInspection.cs

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

Rubberduck.Inspections/QuickFixes/RemoveEmptyIfBlockQuickFix.cs renamed to Rubberduck.Inspections/QuickFixes/RemoveEmptyConditionBlockQuickFix.cs

Lines changed: 19 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,23 +1,23 @@
11
using System;
22
using System.Collections.Generic;
3-
using System.Diagnostics;
43
using System.Linq;
5-
using Antlr4.Runtime;
64
using Rubberduck.Inspections.Concrete;
7-
using Rubberduck.Parsing.Grammar;
5+
using Rubberduck.Parsing.VBA;
86
using Rubberduck.Parsing.Inspections.Abstract;
9-
using Rubberduck.Parsing.Inspections.Resources;
7+
using Rubberduck.Parsing.Grammar;
108
using Rubberduck.Parsing.Rewriter;
11-
using Rubberduck.Parsing.VBA;
9+
using Antlr4.Runtime;
10+
using Rubberduck.Parsing.Inspections.Resources;
11+
using System.Diagnostics;
1212

1313
namespace Rubberduck.Inspections.QuickFixes
1414
{
15-
internal sealed class RemoveEmptyIfBlockQuickFix : IQuickFix
15+
internal sealed class RemoveEmptyConditionBlockQuickFix : IQuickFix
1616
{
17-
private static readonly HashSet<Type> _supportedInspections = new HashSet<Type> { typeof(EmptyIfBlockInspection) };
17+
private static readonly HashSet<Type> _supportedInspections = new HashSet<Type> { typeof(EmptyConditionBlockInspection) };
1818
private readonly RubberduckParserState _state;
1919

20-
public RemoveEmptyIfBlockQuickFix(RubberduckParserState state)
20+
public RemoveEmptyConditionBlockQuickFix(RubberduckParserState state)
2121
{
2222
_state = state;
2323
}
@@ -92,6 +92,16 @@ private void UpdateContext(VBAParser.ElseIfBlockContext context, IModuleRewriter
9292
rewriter.Remove(context);
9393
}
9494

95+
private void UpdateContext(VBAParser.ElseBlockContext context, IModuleRewriter rewriter)
96+
{
97+
var elseBlock = context.block();
98+
99+
if (elseBlock.ChildCount == 0)
100+
{
101+
rewriter.Remove(context);
102+
}
103+
}
104+
95105
private void UpdateCondition(VBAParser.RelationalOpContext condition, IModuleRewriter rewriter)
96106
{
97107
if (condition.EQ() != null)
@@ -178,7 +188,7 @@ private bool FirstBlockStmntHasLabel(VBAParser.BlockContext block)
178188

179189
public string Description(IInspectionResult result)
180190
{
181-
return InspectionsUI.RemoveEmptyIfBlockQuickFix;
191+
return InspectionsUI.RemoveEmptyConditionBlockQuickFix;
182192
}
183193

184194
public bool CanFixInProcedure { get; } = false;

Rubberduck.Inspections/QuickFixes/RemoveEmptyElseBlockQuickFix.cs

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

Rubberduck.Inspections/Rubberduck.Inspections.csproj

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -62,6 +62,7 @@
6262
<Compile Include="Concrete\AssignedByValParameterInspection.cs" />
6363
<Compile Include="Concrete\EmptyBlockInspectionListenerBase.cs" />
6464
<Compile Include="Concrete\EmptyCaseBlockInspection.cs" />
65+
<Compile Include="Concrete\EmptyConditionBlockInspection.cs" />
6566
<Compile Include="Concrete\EmptyDoWhileBlockInspection.cs" />
6667
<Compile Include="Concrete\EmptyForEachBlockInspection.cs" />
6768
<Compile Include="Concrete\EmptyForLoopBlockInspection.cs" />
@@ -73,7 +74,6 @@
7374
<Compile Include="ParseTreeListeners\AttributeAnnotationListener.cs" />
7475
<Compile Include="Concrete\ConstantNotUsedInspection.cs" />
7576
<Compile Include="Concrete\DefaultProjectNameInspection.cs" />
76-
<Compile Include="Concrete\EmptyIfBlockInspection.cs" />
7777
<Compile Include="Concrete\EmptyStringLiteralInspection.cs" />
7878
<Compile Include="Concrete\EncapsulatePublicFieldInspection.cs" />
7979
<Compile Include="Concrete\FunctionReturnValueNotUsedInspection.cs" />
@@ -90,7 +90,6 @@
9090
<Compile Include="Concrete\MissingAttributeInspection.cs" />
9191
<Compile Include="Abstract\InspectionResultBase.cs" />
9292
<Compile Include="Concrete\RedundantByRefModifierInspection.cs" />
93-
<Compile Include="Concrete\EmptyElseBlockInspection.cs" />
9493
<Compile Include="Inspector.cs" />
9594
<Compile Include="Concrete\MemberNotOnInterfaceInspection.cs" />
9695
<Compile Include="Concrete\MissingAnnotationArgumentInspection.cs" />
@@ -118,6 +117,7 @@
118117
<Compile Include="QuickFixes\AssignedByValParameterMakeLocalCopyQuickFix.cs" />
119118
<Compile Include="QuickFixes\ChangeDimToPrivateQuickFix.cs" />
120119
<Compile Include="QuickFixes\ChangeIntegerToLongQuickFix.cs" />
120+
<Compile Include="QuickFixes\RemoveEmptyConditionBlockQuickFix.cs" />
121121
<Compile Include="QuickFixes\RemoveStopKeywordQuickFix.cs" />
122122
<Compile Include="QuickFixes\SpecifyExplicitByRefModifierQuickFix.cs" />
123123
<Compile Include="QuickFixes\ChangeProcedureToFunctionQuickFix.cs" />
@@ -132,8 +132,6 @@
132132
<Compile Include="QuickFixes\PassParameterByReferenceQuickFix.cs" />
133133
<Compile Include="QuickFixes\PassParameterByValueQuickFix.cs" />
134134
<Compile Include="QuickFixes\RemoveCommentQuickFix.cs" />
135-
<Compile Include="QuickFixes\RemoveEmptyElseBlockQuickFix.cs" />
136-
<Compile Include="QuickFixes\RemoveEmptyIfBlockQuickFix.cs" />
137135
<Compile Include="QuickFixes\RemoveExplicitCallStatmentQuickFix.cs" />
138136
<Compile Include="QuickFixes\RemoveExplicitLetStatementQuickFix.cs" />
139137
<Compile Include="QuickFixes\RemoveOptionBaseStatementQuickFix.cs" />

0 commit comments

Comments
 (0)