Skip to content

Commit 8c4325b

Browse files
committed
added quickfix xmldoc, R-W
1 parent f3caa74 commit 8c4325b

33 files changed

+1016
-8
lines changed

Rubberduck.CodeAnalysis/QuickFixes/RemoveAnnotationQuickFix.cs

Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,36 @@
66

77
namespace Rubberduck.Inspections.QuickFixes
88
{
9+
/// <summary>
10+
/// Removes an annotation comment representing a hidden module or member attribute, in order to maintain consistency between hidden attributes and annotation comments.
11+
/// </summary>
12+
/// <inspections>
13+
/// <inspection name="MissingAttributeInspection" />
14+
/// </inspections>
15+
/// <canfix procedure="false" module="false" project="false" />
16+
/// <example>
17+
/// <before>
18+
/// <![CDATA[
19+
/// Attribute VB_PredeclaredId = False
20+
/// '@PredeclaredId
21+
///
22+
/// Option Explicit
23+
///
24+
/// Public Sub DoSomething()
25+
/// End Sub
26+
/// ]]>
27+
/// </before>
28+
/// <after>
29+
/// <![CDATA[
30+
/// Attribute VB_PredeclaredId = False
31+
///
32+
/// Option Explicit
33+
///
34+
/// Public Sub DoSomething()
35+
/// End Sub
36+
/// ]]>
37+
/// </after>
38+
/// </example>
939
public sealed class RemoveAnnotationQuickFix : QuickFixBase
1040
{
1141
private readonly IAnnotationUpdater _annotationUpdater;

Rubberduck.CodeAnalysis/QuickFixes/RemoveAttributeQuickFix.cs

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,35 @@
99

1010
namespace Rubberduck.Inspections.QuickFixes
1111
{
12+
/// <summary>
13+
/// Removes a hidden attribute, in order to maintain consistency between hidden attributes and (missing) annotation comments.
14+
/// </summary>
15+
/// <inspections>
16+
/// <inspection name="MissingModuleAnnotationInspection" />
17+
/// <inspection name="MissingMemberAnnotationInspection" />
18+
/// </inspections>
19+
/// <canfix procedure="false" module="false" project="false" />
20+
/// <example>
21+
/// <before>
22+
/// <![CDATA[
23+
/// Option Explicit
24+
///
25+
/// Public Sub DoSomething()
26+
/// Attribute VB_UserMemId = 0
27+
///
28+
/// End Sub
29+
/// ]]>
30+
/// </before>
31+
/// <after>
32+
/// <![CDATA[
33+
/// Option Explicit
34+
///
35+
/// Public Sub DoSomething()
36+
///
37+
/// End Sub
38+
/// ]]>
39+
/// </after>
40+
/// </example>
1241
public class RemoveAttributeQuickFix : QuickFixBase
1342
{
1443
private readonly IAttributesUpdater _attributesUpdater;

Rubberduck.CodeAnalysis/QuickFixes/RemoveCommentQuickFix.cs

Lines changed: 28 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,33 @@
55

66
namespace Rubberduck.Inspections.QuickFixes
77
{
8+
/// <summary>
9+
/// Removes a comment.
10+
/// </summary>
11+
/// <inspections>
12+
/// <inspection name="ObsoleteCommentSyntaxInspection" />
13+
/// </inspections>
14+
/// <canfix procedure="true" module="true" project="true" />
15+
/// <example>
16+
/// <before>
17+
/// <![CDATA[
18+
/// Option Explicit
19+
///
20+
/// Public Sub DoSomething()
21+
/// Rem does something
22+
/// End Sub
23+
/// ]]>
24+
/// </before>
25+
/// <after>
26+
/// <![CDATA[
27+
/// Option Explicit
28+
///
29+
/// Public Sub DoSomething()
30+
///
31+
/// End Sub
32+
/// ]]>
33+
/// </after>
34+
/// </example>
835
public sealed class RemoveCommentQuickFix : QuickFixBase
936
{
1037
public RemoveCommentQuickFix()
@@ -17,7 +44,7 @@ public override void Fix(IInspectionResult result, IRewriteSession rewriteSessio
1744
rewriter.Remove(result.Context);
1845
}
1946

20-
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.RemoveObsoleteStatementQuickFix;
47+
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.RemoveCommentQuickFix;
2148

2249
public override bool CanFixInProcedure => true;
2350
public override bool CanFixInModule => true;

Rubberduck.CodeAnalysis/QuickFixes/RemoveDuplicatedAnnotationQuickFix.cs

Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,34 @@
77

88
namespace Rubberduck.Inspections.QuickFixes
99
{
10+
/// <summary>
11+
/// Removes a duplicated annotation comment.
12+
/// </summary>
13+
/// <inspections>
14+
/// <inspection name="DuplicatedAnnotationInspection" />
15+
/// </inspections>
16+
/// <canfix procedure="true" module="true" project="true" />
17+
/// <example>
18+
/// <before>
19+
/// <![CDATA[
20+
/// Option Explicit
21+
///
22+
/// '@Obsolete
23+
/// '@Obsolete
24+
/// Public Sub DoSomething()
25+
/// End Sub
26+
/// ]]>
27+
/// </before>
28+
/// <after>
29+
/// <![CDATA[
30+
/// Option Explicit
31+
///
32+
/// '@Obsolete
33+
/// Public Sub DoSomething()
34+
/// End Sub
35+
/// ]]>
36+
/// </after>
37+
/// </example>
1038
public sealed class RemoveDuplicatedAnnotationQuickFix : QuickFixBase
1139
{
1240
private readonly IAnnotationUpdater _annotationUpdater;

Rubberduck.CodeAnalysis/QuickFixes/RemoveEmptyElseBlockQuickFix.cs

Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,38 @@
66

77
namespace Rubberduck.Inspections.QuickFixes
88
{
9+
/// <summary>
10+
/// Removes an empty Else block.
11+
/// </summary>
12+
/// <inspections>
13+
/// <inspection name="EmptyElseBlockInspection" />
14+
/// </inspections>
15+
/// <canfix procedure="false" module="false" project="false" />
16+
/// <example>
17+
/// <before>
18+
/// <![CDATA[
19+
/// Option Explicit
20+
///
21+
/// Public Sub DoSomething()
22+
/// If Application.Calculation = xlCalculationAutomatic Then
23+
/// Application.Calculation = xlCalculationManual
24+
/// Else
25+
/// End If
26+
/// End Sub
27+
/// ]]>
28+
/// </before>
29+
/// <after>
30+
/// <![CDATA[
31+
/// Option Explicit
32+
///
33+
/// Public Sub DoSomething()
34+
/// If Application.Calculation = xlCalculationAutomatic Then
35+
/// Application.Calculation = xlCalculationManual
36+
/// End If
37+
/// End Sub
38+
/// ]]>
39+
/// </after>
40+
/// </example>
941
public sealed class RemoveEmptyElseBlockQuickFix : QuickFixBase
1042
{
1143
public RemoveEmptyElseBlockQuickFix()

Rubberduck.CodeAnalysis/QuickFixes/RemoveEmptyIfBlockQuickFix.cs

Lines changed: 35 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,41 @@
1010

1111
namespace Rubberduck.Inspections.QuickFixes
1212
{
13+
/// <summary>
14+
/// Removes an empty conditional block by inverting the condition expression.
15+
/// </summary>
16+
/// <inspections>
17+
/// <inspection name="EmptyIfBlockInspection" />
18+
/// </inspections>
19+
/// <canfix procedure="false" module="false" project="false" />
20+
/// <example>
21+
/// <before>
22+
/// <![CDATA[
23+
/// Option Explicit
24+
///
25+
/// Public Sub DoSomething()
26+
/// If Application.Calculation = xlCalculationManual Then
27+
/// Else
28+
/// Application.Calculation = xlCalculationManual
29+
/// End If
30+
/// '...
31+
/// End Sub
32+
/// ]]>
33+
/// </before>
34+
/// <after>
35+
/// <![CDATA[
36+
/// Option Explicit
37+
///
38+
/// Public Sub DoSomething()
39+
/// If Application.Calculation <> xlCalculationManual Then
40+
///
41+
/// Application.Calculation = xlCalculationManual
42+
/// End If
43+
/// '...
44+
/// End Sub
45+
/// ]]>
46+
/// </after>
47+
/// </example>
1348
public sealed class RemoveEmptyIfBlockQuickFix : QuickFixBase
1449
{
1550
public RemoveEmptyIfBlockQuickFix()

Rubberduck.CodeAnalysis/QuickFixes/RemoveExplicitByRefModifierQuickFix.cs

Lines changed: 27 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,10 +8,36 @@
88
using Rubberduck.Parsing.Rewriter;
99
using Rubberduck.Parsing.Symbols;
1010
using Rubberduck.Parsing.VBA;
11-
using Rubberduck.Parsing.VBA.Extensions;
1211

1312
namespace Rubberduck.Inspections.QuickFixes
1413
{
14+
/// <summary>
15+
/// Removes an explicit ByRef modifier, making it implicit.
16+
/// </summary>
17+
/// <inspections>
18+
/// <inspection name="RedundantByRefModifierInspection" />
19+
/// </inspections>
20+
/// <canfix procedure="true" module="true" project="true" />
21+
/// <example>
22+
/// <before>
23+
/// <![CDATA[
24+
/// Option Explicit
25+
///
26+
/// Public Sub DoSomething(ByRef value As Long)
27+
/// '...
28+
/// End Sub
29+
/// ]]>
30+
/// </before>
31+
/// <after>
32+
/// <![CDATA[
33+
/// Option Explicit
34+
///
35+
/// Public Sub DoSomething(value As Long)
36+
/// '...
37+
/// End Sub
38+
/// ]]>
39+
/// </after>
40+
/// </example>
1541
public sealed class RemoveExplicitByRefModifierQuickFix : QuickFixBase
1642
{
1743
private readonly IDeclarationFinderProvider _declarationFinderProvider;

Rubberduck.CodeAnalysis/QuickFixes/RemoveExplicitCallStatementQuickFix.cs

Lines changed: 35 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,41 @@
66

77
namespace Rubberduck.Inspections.QuickFixes
88
{
9+
/// <summary>
10+
/// Makes a call statement implicit by removing the 'Call' keyword, adjusting argument list parentheses accordingly.
11+
/// </summary>
12+
/// <inspections>
13+
/// <inspection name="ObsoleteCallStatementInspection" />
14+
/// </inspections>
15+
/// <canfix procedure="true" module="true" project="true" />
16+
/// <example>
17+
/// <before>
18+
/// <![CDATA[
19+
/// Option Explicit
20+
///
21+
/// Public Sub DoSomething()
22+
/// Call DoSomethingElse(42)
23+
/// End Sub
24+
///
25+
/// Private Sub DoSomethingElse(ByVal value As Long)
26+
/// Debug.Print value
27+
/// End Sub
28+
/// ]]>
29+
/// </before>
30+
/// <after>
31+
/// <![CDATA[
32+
/// Option Explicit
33+
///
34+
/// Public Sub DoSomething()
35+
/// DoSomethingElse 42
36+
/// End Sub
37+
///
38+
/// Private Sub DoSomethingElse(ByVal value As Long)
39+
/// Debug.Print value
40+
/// End Sub
41+
/// ]]>
42+
/// </after>
43+
/// </example>
944
public sealed class RemoveExplicitCallStatementQuickFix : QuickFixBase
1045
{
1146
public RemoveExplicitCallStatementQuickFix()

Rubberduck.CodeAnalysis/QuickFixes/RemoveExplicitLetStatementQuickFix.cs

Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,37 @@
77

88
namespace Rubberduck.Inspections.QuickFixes
99
{
10+
/// <summary>
11+
/// Makes the 'Let' keyword of a value assignment implicit.
12+
/// </summary>
13+
/// <inspections>
14+
/// <inspection name="ObsoleteLetStatementInspection" />
15+
/// </inspections>
16+
/// <canfix procedure="true" module="true" project="true" />
17+
/// <example>
18+
/// <before>
19+
/// <![CDATA[
20+
/// Option Explicit
21+
///
22+
/// Public Sub DoSomething()
23+
/// Dim value As Long
24+
/// Let value = 42
25+
/// Debug.Print value
26+
/// End Sub
27+
/// ]]>
28+
/// </before>
29+
/// <after>
30+
/// <![CDATA[
31+
/// Option Explicit
32+
///
33+
/// Public Sub DoSomething()
34+
/// Dim value As Long
35+
/// value = 42
36+
/// Debug.Print value
37+
/// End Sub
38+
/// ]]>
39+
/// </after>
40+
/// </example>
1041
public sealed class RemoveExplicitLetStatementQuickFix : QuickFixBase
1142
{
1243
public RemoveExplicitLetStatementQuickFix()

Rubberduck.CodeAnalysis/QuickFixes/RemoveLocalErrorQuickFix.cs

Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,45 @@
66

77
namespace Rubberduck.Inspections.QuickFixes
88
{
9+
/// <summary>
10+
/// Makes the 'Local' keyword of an 'On Error' statement implicit.
11+
/// </summary>
12+
/// <inspections>
13+
/// <inspection name="OnLocalErrorInspection" />
14+
/// </inspections>
15+
/// <canfix procedure="true" module="true" project="true" />
16+
/// <example>
17+
/// <before>
18+
/// <![CDATA[
19+
/// Option Explicit
20+
///
21+
/// Public Sub DoSomething()
22+
/// On Local Error GoTo CleanFail
23+
/// Debug.Print 42 / 0
24+
/// CleanExit:
25+
/// Exit Sub
26+
/// CleanFail:
27+
/// Debug.Print Err.Description
28+
/// Resume CleanExit
29+
/// End Sub
30+
/// ]]>
31+
/// </before>
32+
/// <after>
33+
/// <![CDATA[
34+
/// Option Explicit
35+
///
36+
/// Public Sub DoSomething()
37+
/// On Error GoTo CleanFail
38+
/// Debug.Print 42 / 0
39+
/// CleanExit:
40+
/// Exit Sub
41+
/// CleanFail:
42+
/// Debug.Print Err.Description
43+
/// Resume CleanExit
44+
/// End Sub
45+
/// ]]>
46+
/// </after>
47+
/// </example>
948
public sealed class RemoveLocalErrorQuickFix : QuickFixBase
1049
{
1150
public RemoveLocalErrorQuickFix()

0 commit comments

Comments
 (0)