Skip to content

Commit aa3dcd2

Browse files
retailcoderIvenBachBZngrbclothierRsge
authored
Sync w/upstream (#255)
Co-authored-by: IvenBach <[email protected]> Co-authored-by: Brian Zenger <[email protected]> Co-authored-by: bclothier <[email protected]> Co-authored-by: Jan <[email protected]> Co-authored-by: Clemens Lieb <[email protected]> Co-authored-by: Andreas Waigel <[email protected]> Co-authored-by: Rubberduck Release Bot <[email protected]> Co-authored-by: Max Doerner <[email protected]> Co-authored-by: doterik <[email protected]> Co-authored-by: Andreas Waigel <[email protected]> Co-authored-by: PhilCattivocarattere <[email protected]>
1 parent f121ba8 commit aa3dcd2

File tree

145 files changed

+10693
-1091
lines changed

Some content is hidden

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

145 files changed

+10693
-1091
lines changed

README.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
![banner](https://user-images.githubusercontent.com/5751684/113501222-8edfe880-94f1-11eb-99a9-64583e413ef3.png)
1+
<!-- ![banner](https://user-images.githubusercontent.com/5751684/113501222-8edfe880-94f1-11eb-99a9-64583e413ef3.png) -->
22

33
[**Installing**](https://github.com/rubberduck-vba/Rubberduck/wiki/Installing)[Contributing](https://github.com/rubberduck-vba/Rubberduck/blob/next/CONTRIBUTING.md)[Attributions](https://github.com/rubberduck-vba/Rubberduck/blob/next/docs/Attributions.md)[Blog](https://rubberduckvba.blog)[Wiki](https://github.com/rubberduck-vba/Rubberduck/wiki)[rubberduckvba.com](https://rubberduckvba.com)
44

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyMethodInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
3333
/// ]]>
3434
/// </module>
3535
/// </example>
36-
internal class EmptyMethodInspection : DeclarationInspectionBase
36+
internal sealed class EmptyMethodInspection : DeclarationInspectionBase
3737
{
3838
public EmptyMethodInspection(IDeclarationFinderProvider declarationFinderProvider)
3939
: base(declarationFinderProvider, DeclarationType.Member)

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyModuleInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -84,7 +84,7 @@ public override bool VisitModuleDeclarations(VBAParser.ModuleDeclarationsContext
8484
public override bool VisitModuleDeclarationsElement(VBAParser.ModuleDeclarationsElementContext context)
8585
{
8686
return context.moduleVariableStmt() == null
87-
&& context.constStmt() == null
87+
&& context.moduleConstStmt() == null
8888
&& context.enumerationStmt() == null
8989
&& context.udtDeclaration() == null
9090
&& context.eventStmt() == null

Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -13,8 +13,8 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
1313
/// Warns about 'Sub' procedures that could be refactored into a 'Function'.
1414
/// </summary>
1515
/// <why>
16-
/// Idiomatic VB code uses 'Function' procedures to return a single value. If the procedure isn't side-effecting, consider writing is as a
17-
/// 'Function' rather than a 'Sub' the returns a result through a 'ByRef' parameter.
16+
/// Idiomatic VB code uses 'Function' procedures to return a single value. If the procedure isn't side-effecting, consider writing it as a
17+
/// 'Function' rather than a 'Sub' that returns a result through a 'ByRef' parameter.
1818
/// </why>
1919
/// <example hasResult="true">
2020
/// <module name="MyModule" type="Standard Module">
Lines changed: 83 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,83 @@
1+
using Rubberduck.CodeAnalysis.Inspections.Abstract;
2+
using Rubberduck.Parsing.Symbols;
3+
using Rubberduck.Parsing.VBA;
4+
using Rubberduck.Parsing.VBA.DeclarationCaching;
5+
using Rubberduck.Resources.Inspections;
6+
using Rubberduck.VBEditor.SafeComWrappers;
7+
using System;
8+
using System.Collections.Generic;
9+
using System.Linq;
10+
11+
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
12+
{
13+
/// <summary>
14+
/// Identifies public enumerations declared within worksheet modules.
15+
/// </summary>
16+
/// <why>
17+
/// Copying a worksheet which contains a public Enum declaration will also create a copy of the Enum declaration.
18+
/// The copied Enum declaration will result in an 'Ambiguous name detected' compiler error.
19+
/// Declaring Enumerations in Standard or Class modules avoids unintentional duplication of an Enum declaration.
20+
/// </why>
21+
/// <example hasResult="true">
22+
/// <module name="WorksheetModule" type="Document Module">
23+
/// <![CDATA[
24+
/// Public Enum ExampleEnum
25+
/// FirstEnum = 0
26+
/// SecondEnum
27+
/// End Enum
28+
/// ]]>
29+
/// </module>
30+
/// </example>
31+
/// <example hasResult="false">
32+
/// <module name="WorksheetModule" type="Document Module">
33+
/// <![CDATA[
34+
/// Private Enum ExampleEnum
35+
/// FirstEnum = 0
36+
/// SecondEnum
37+
/// End Enum
38+
/// ]]>
39+
/// </module>
40+
/// </example>
41+
internal sealed class PublicEnumerationDeclaredInWorksheetInspection : DeclarationInspectionBase
42+
{
43+
private readonly string[] _worksheetSuperTypeNames = new string[] { "Worksheet", "_Worksheet" };
44+
45+
public PublicEnumerationDeclaredInWorksheetInspection(IDeclarationFinderProvider declarationFinderProvider)
46+
: base(declarationFinderProvider, DeclarationType.Enumeration)
47+
{}
48+
49+
protected override bool IsResultDeclaration(Declaration enumeration, DeclarationFinder finder)
50+
{
51+
if (enumeration.Accessibility != Accessibility.Private
52+
&& enumeration.QualifiedModuleName.ComponentType == ComponentType.Document)
53+
{
54+
if (enumeration.ParentDeclaration is ClassModuleDeclaration classModuleDeclaration)
55+
{
56+
return RetrieveSuperTypeNames(classModuleDeclaration).Intersect(_worksheetSuperTypeNames).Any();
57+
}
58+
}
59+
60+
return false;
61+
}
62+
63+
protected override string ResultDescription(Declaration declaration)
64+
{
65+
return string.Format(InspectionResults.PublicEnumerationDeclaredInWorksheetInspection,
66+
declaration.IdentifierName);
67+
}
68+
69+
/// <summary>
70+
/// Supports property injection for testing.
71+
/// </summary>
72+
/// <remarks>
73+
/// MockParser does not populate SuperTypes/SuperTypeNames. RetrieveSuperTypeNames Func allows injection
74+
/// of ClassModuleDeclaration.SuperTypeNames property results.
75+
/// </remarks>
76+
public Func<ClassModuleDeclaration, IEnumerable<string>> RetrieveSuperTypeNames { set; private get; } = GetSuperTypeNames;
77+
78+
private static IEnumerable<string> GetSuperTypeNames(ClassModuleDeclaration classModule)
79+
{
80+
return classModule.SupertypeNames;
81+
}
82+
}
83+
}

Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -229,9 +229,6 @@ private static string ComponentPropertyValue(IVBComponent component, string prop
229229
return null;
230230
}
231231

232-
protected override string ResultDescription(IdentifierReference reference, string codeName)
233-
{
234-
return InspectionResults.SheetAccessedUsingStringInspection;
235-
}
232+
protected override string ResultDescription(IdentifierReference reference, string codeName) => InspectionResults.SheetAccessedUsingStringInspection;
236233
}
237234
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/KeywordsUsedAsMemberInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete.ThunderCode
1919
/// While perfectly legal as Type or Enum member names, these identifiers should be avoided:
2020
/// they need to be square-bracketed everywhere they are used.
2121
/// </why>
22-
internal class KeywordsUsedAsMemberInspection : DeclarationInspectionBase
22+
internal sealed class KeywordsUsedAsMemberInspection : DeclarationInspectionBase
2323
{
2424
public KeywordsUsedAsMemberInspection(IDeclarationFinderProvider declarationFinderProvider)
2525
: base(declarationFinderProvider, DeclarationType.EnumerationMember, DeclarationType.UserDefinedTypeMember)

Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NonBreakingSpaceIdentifierInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete.ThunderCode
1414
/// code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver.
1515
/// This inspection may accidentally reveal non-breaking spaces in code copied and pasted from a website.
1616
/// </why>
17-
internal class NonBreakingSpaceIdentifierInspection : DeclarationInspectionBase
17+
internal sealed class NonBreakingSpaceIdentifierInspection : DeclarationInspectionBase
1818
{
1919
private const string Nbsp = "\u00A0";
2020

Lines changed: 83 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,83 @@
1+
using Rubberduck.CodeAnalysis.Inspections.Abstract;
2+
using Rubberduck.CodeAnalysis.Inspections.Extensions;
3+
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.Parsing.VBA.DeclarationCaching;
6+
using Rubberduck.Resources.Inspections;
7+
using System.Linq;
8+
9+
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
10+
{
11+
/// <summary>
12+
/// Warns about User Defined Type (UDT) members that are never referenced.
13+
/// </summary>
14+
/// <why>
15+
/// Declarations that are never used should be removed.
16+
/// </why>
17+
/// <example hasResult="true">
18+
/// <module name="MyModule" type="Standard Module">
19+
/// <![CDATA[
20+
/// Private Type TTestModule
21+
/// FirstVal As Long
22+
/// End Type
23+
///
24+
/// Private this As TTestModule
25+
/// ]]>
26+
/// </module>
27+
/// </example>
28+
/// <example hasResult="false">
29+
/// <module name="MyModule" type="Standard Module">
30+
/// <![CDATA[
31+
/// Private Type TTestModule
32+
/// FirstVal As Long
33+
/// End Type
34+
///
35+
/// Private this As TTestModule
36+
///
37+
/// 'UDT Member is assigned but not used
38+
/// Public Sub DoSomething()
39+
/// this.FirstVal = 42
40+
/// End Sub
41+
/// ]]>
42+
/// </module>
43+
/// </example>
44+
/// <example hasResult="false">
45+
/// <module name="MyModule" type="Standard Module">
46+
/// <![CDATA[
47+
/// Private Type TTestModule
48+
/// FirstVal As Long
49+
/// End Type
50+
///
51+
/// Private this As TTestModule
52+
///
53+
/// 'UDT Member is assigned and read
54+
/// Public Sub DoSomething()
55+
/// this.FirstVal = 42
56+
/// Debug.Print this.FirstVal
57+
/// End Sub
58+
/// ]]>
59+
/// </module>
60+
/// </example>
61+
internal sealed class UDTMemberNotUsedInspection : DeclarationInspectionBase
62+
{
63+
public UDTMemberNotUsedInspection(IDeclarationFinderProvider declarationFinderProvider)
64+
: base(declarationFinderProvider, DeclarationType.UserDefinedTypeMember)
65+
{}
66+
67+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
68+
{
69+
return declaration.DeclarationType.Equals(DeclarationType.UserDefinedTypeMember)
70+
&& !declaration.References.Any();
71+
}
72+
73+
protected override string ResultDescription(Declaration declaration)
74+
{
75+
var declarationType = declaration.DeclarationType.ToLocalizedString();
76+
var declarationName = declaration.IdentifierName;
77+
return string.Format(
78+
InspectionResults.IdentifierNotUsedInspection,
79+
declarationType,
80+
declarationName);
81+
}
82+
}
83+
}

Rubberduck.CodeAnalysis/QuickFixes/Abstract/QuickFixBase.cs

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,22 @@ public void RemoveInspections(params Type[] inspections)
5555
public virtual CodeKind TargetCodeKind => CodeKind.CodePaneCode;
5656

5757
public abstract void Fix(IInspectionResult result, IRewriteSession rewriteSession);
58+
59+
/// <summary>
60+
/// FixMany defers the enumeration of inspection results to the QuickFix
61+
/// </summary>
62+
/// <remarks>
63+
/// The default implementation enumerates the results collection calling Fix() for each result.
64+
/// Override this funcion when a QuickFix needs operate on results as a group (e.g., RemoveUnusedDeclarationQuickFix)
65+
/// </remarks>
66+
public virtual void Fix(IReadOnlyCollection<IInspectionResult> results, IRewriteSession rewriteSession)
67+
{
68+
foreach (var result in results)
69+
{
70+
Fix(result, rewriteSession);
71+
}
72+
}
73+
5874
public abstract string Description(IInspectionResult result);
5975

6076
public abstract bool CanFixMultiple { get; }

0 commit comments

Comments
 (0)