diff --git a/Rubberduck.CodeAnalysis/Inspections/Abstract/IsMissingInspectionBase.cs b/Rubberduck.CodeAnalysis/Inspections/Abstract/IsMissingInspectionBase.cs index 14fcb8b4ba..24b0d56b00 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Abstract/IsMissingInspectionBase.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Abstract/IsMissingInspectionBase.cs @@ -31,7 +31,7 @@ protected IReadOnlyList IsMissingDeclarations if (isMissing.Count == 0) { - _logger.Trace("No 'IsMissing' Declarations were not found in IsMissingInspectionBase."); + _logger.Trace("No 'IsMissing' Declarations were found in IsMissingInspectionBase."); } return isMissing; diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignedByValParameterInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignedByValParameterInspection.cs index 91bf05d295..100833a3f7 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignedByValParameterInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignedByValParameterInspection.cs @@ -10,6 +10,32 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about parameters passed by value being assigned a new value in the body of a procedure. + /// + /// + /// Debugging is easier if the procedure's initial state is preserved and accessible anywhere within its scope. + /// Mutating the inputs destroys the initial state, and makes the intent ambiguous: if the calling code is meant + /// to be able to access the modified values, then the parameter should be passed ByRef; the ByVal modifier might be a bug. + /// + /// + /// + /// + /// + /// + /// public sealed class AssignedByValParameterInspection : InspectionBase { public AssignedByValParameterInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs index 7de1121799..e0508a3db1 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs @@ -12,6 +12,30 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about a variable that is assigned, and then re-assigned before the first assignment is read. + /// + /// + /// The first assignment is likely redundant, since it is being overwritten by the second. + /// + /// + /// + /// + /// + /// + /// public sealed class AssignmentNotUsedInspection : InspectionBase { private readonly Walker _walker; diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs index 82e6ced03b..af6225a8b9 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs @@ -13,6 +13,31 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Indicates that the value of a hidden VB attribute is out of sync with the corresponding Rubberduck annotation comment. + /// + /// + /// Keeping Rubberduck annotation comments in sync with the hidden VB attribute values, surfaces these hidden attributes in the VBE code panes; + /// Rubberduck can rewrite the attributes to match the corresponding annotation comment. + /// + /// + /// + /// + /// + /// + /// [CannotAnnotate] public sealed class AttributeValueOutOfSyncInspection : InspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/BooleanAssignedInIfElseInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/BooleanAssignedInIfElseInspection.cs index 11ca913cb2..339747e03f 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/BooleanAssignedInIfElseInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/BooleanAssignedInIfElseInspection.cs @@ -13,6 +13,30 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies redundant Boolean expressions in conditionals. + /// + /// + /// A Boolean expression never needs to be compared to a Boolean literal in a conditional expression. + /// + /// + /// + /// + /// + /// + /// public sealed class BooleanAssignedInIfElseInspection : ParseTreeInspectionBase { public BooleanAssignedInIfElseInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ConstantNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ConstantNotUsedInspection.cs index 25567fc285..5098ff1dc7 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ConstantNotUsedInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ConstantNotUsedInspection.cs @@ -13,6 +13,30 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates 'Const' declarations that are never referenced. + /// + /// + /// Declarations that are never used should be removed. + /// + /// + /// + /// + /// + /// + /// public sealed class ConstantNotUsedInspection : InspectionBase { public ConstantNotUsedInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/DefTypeStatementInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/DefTypeStatementInspection.cs index b97f18decb..d1a44182f2 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/DefTypeStatementInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/DefTypeStatementInspection.cs @@ -14,6 +14,23 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about Def[Type] statements. + /// + /// + /// These declarative statements make the first letter of identifiers determine the data type. + /// + /// + /// + /// public sealed class DefTypeStatementInspection : ParseTreeInspectionBase { public DefTypeStatementInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/DefaultProjectNameInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/DefaultProjectNameInspection.cs index fadeecf17b..4e43bd4981 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/DefaultProjectNameInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/DefaultProjectNameInspection.cs @@ -9,6 +9,12 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// This inspection means to indicate when the project has not been renamed. + /// + /// + /// VBA projects should be meaningfully named, to avoid namespace clashes when referencing other VBA projects. + /// [CannotAnnotate] public sealed class DefaultProjectNameInspection : InspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs index d47b368d69..dec1245a55 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs @@ -8,6 +8,31 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about duplicated annotations. + /// + /// + /// Rubberduck annotations should not be specified more than once for a given module, member, variable, or expression. + /// + /// + /// + /// + /// + /// + /// public sealed class DuplicatedAnnotationInspection : InspectionBase { public DuplicatedAnnotationInspection(RubberduckParserState state) : base(state) @@ -27,12 +52,9 @@ protected override IEnumerable DoGetInspectionResults() issues.AddRange(duplicateAnnotations.Select(duplicate => { var result = new DeclarationInspectionResult( - this, - string.Format(InspectionResults.DuplicatedAnnotationInspection, duplicate.Key.ToString()), - declaration); + this, string.Format(InspectionResults.DuplicatedAnnotationInspection, duplicate.Key.ToString()), declaration); result.Properties.AnnotationType = duplicate.Key; - return result; })); } diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyCaseBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyCaseBlockInspection.cs index 2bcf3a7061..fe8ee8d570 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyCaseBlockInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyCaseBlockInspection.cs @@ -13,6 +13,35 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies empty 'Case' blocks that can be safely removed. + /// + /// + /// Case blocks in VBA do not "fall through"; an empty 'Case' block might be hiding a bug. + /// + /// + /// 0 + /// Debug.Print foo ' does not run if foo is 0. + /// End Select + /// End Sub + /// ]]> + /// + /// + /// 0 + /// '...code... + /// End Select + /// End Sub + /// ]]> + /// [Experimental(nameof(ExperimentalNames.EmptyBlockInspections))] internal class EmptyCaseBlockInspection : ParseTreeInspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyDoWhileBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyDoWhileBlockInspection.cs index b5ac732634..0f6a47110d 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyDoWhileBlockInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyDoWhileBlockInspection.cs @@ -13,6 +13,30 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies empty 'Do...Loop While' blocks that can be safely removed. + /// + /// + /// Dead code should be removed. A loop without a body is usually redundant. + /// + /// + /// + /// + /// + /// + /// [Experimental(nameof(ExperimentalNames.EmptyBlockInspections))] internal class EmptyDoWhileBlockInspection : ParseTreeInspectionBase { @@ -23,13 +47,11 @@ protected override IEnumerable DoGetInspectionResults() { return Listener.Contexts .Where(result => !result.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName)) - .Select(result => new QualifiedContextInspectionResult(this, - InspectionResults.EmptyDoWhileBlockInspection, - result)); + .Select(result => + new QualifiedContextInspectionResult(this, InspectionResults.EmptyDoWhileBlockInspection, result)); } - public override IInspectionListener Listener { get; } = - new EmptyDoWhileBlockListener(); + public override IInspectionListener Listener { get; } = new EmptyDoWhileBlockListener(); public class EmptyDoWhileBlockListener : EmptyBlockInspectionListenerBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyElseBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyElseBlockInspection.cs index 64035a416b..892405ca8f 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyElseBlockInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyElseBlockInspection.cs @@ -13,6 +13,32 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies empty 'Else' blocks that can be safely removed. + /// + /// + /// Empty code blocks are redundant, dead code that should be removed. They can also be misleading about their intent: + /// an empty block may be signalling an unfinished thought or an oversight. + /// + /// + /// + /// + /// + /// + /// [Experimental(nameof(ExperimentalNames.EmptyBlockInspections))] internal class EmptyElseBlockInspection : ParseTreeInspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForEachBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForEachBlockInspection.cs index 0038c79ba7..4c047affd2 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForEachBlockInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForEachBlockInspection.cs @@ -13,6 +13,32 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies empty 'For Each...Next' blocks that can be safely removed. + /// + /// + /// Dead code should be removed. A loop without a body is usually redundant. + /// + /// + /// + /// + /// + /// + /// [Experimental(nameof(ExperimentalNames.EmptyBlockInspections))] internal class EmptyForEachBlockInspection : ParseTreeInspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForLoopBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForLoopBlockInspection.cs index f481e4a0f2..9e65d808be 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForLoopBlockInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForLoopBlockInspection.cs @@ -13,6 +13,32 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies empty 'For...Next' blocks that can be safely removed. + /// + /// + /// Dead code should be removed. A loop without a body is usually redundant. + /// + /// + /// + /// + /// + /// + /// [Experimental(nameof(ExperimentalNames.EmptyBlockInspections))] internal class EmptyForLoopBlockInspection : ParseTreeInspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyIfBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyIfBlockInspection.cs index 8c21ab60da..37ba08f632 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyIfBlockInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyIfBlockInspection.cs @@ -15,6 +15,31 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies empty 'If' blocks. + /// + /// + /// Conditional expression is inverted; there would not be a need for an 'Else' block otherwise. + /// + /// + /// + /// + /// + /// + /// [Experimental(nameof(ExperimentalNames.EmptyBlockInspections))] internal class EmptyIfBlockInspection : ParseTreeInspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyModuleInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyModuleInspection.cs index aec1807f34..a77189bffa 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyModuleInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyModuleInspection.cs @@ -13,7 +13,12 @@ namespace Rubberduck.Inspections.Concrete { - + /// + /// Flags empty code modules. + /// + /// + /// An empty module does not need to exist and can be safely removed. + /// public sealed class EmptyModuleInspection : InspectionBase { private readonly EmptyModuleVisitor _emptyModuleVisitor; diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyStringLiteralInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyStringLiteralInspection.cs index 749e463617..617fbbbf49 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyStringLiteralInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyStringLiteralInspection.cs @@ -13,6 +13,32 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Flags uses of an empty string literal (""). + /// + /// + /// Standard library constant 'vbNullString' is more explicit about its intent, and should be preferred to a string literal. + /// While the memory gain is meaningless, an empty string literal still takes up 2 bytes of memory, + /// but 'vbNullString' is a null string pointer, and doesn't. + /// + /// + /// + /// + /// + /// + /// public sealed class EmptyStringLiteralInspection : ParseTreeInspectionBase { public EmptyStringLiteralInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyWhileWendBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyWhileWendBlockInspection.cs index 736b093af1..c5779406cf 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyWhileWendBlockInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyWhileWendBlockInspection.cs @@ -13,6 +13,30 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies empty 'While...Wend' blocks that can be safely removed. + /// + /// + /// Dead code should be removed. A loop without a body is usually redundant. + /// + /// + /// + /// + /// + /// + /// [Experimental(nameof(ExperimentalNames.EmptyBlockInspections))] internal class EmptyWhileWendBlockInspection : ParseTreeInspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EncapsulatePublicFieldInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EncapsulatePublicFieldInspection.cs index 58d556e4e6..c20713057d 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EncapsulatePublicFieldInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EncapsulatePublicFieldInspection.cs @@ -10,6 +10,27 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Flags publicly exposed instance fields. + /// + /// + /// Instance fields are the implementation details of a object's internal state; exposing them directly breaks encapsulation. + /// Often, an object only needs to expose a 'Get' procedure to expose an internal instance field. + /// + /// + /// + /// + /// + /// + /// public sealed class EncapsulatePublicFieldInspection : InspectionBase { public EncapsulatePublicFieldInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ApplicationWorksheetFunctionInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ApplicationWorksheetFunctionInspection.cs similarity index 52% rename from Rubberduck.CodeAnalysis/Inspections/Concrete/ApplicationWorksheetFunctionInspection.cs rename to Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ApplicationWorksheetFunctionInspection.cs index a9a20061d3..77f9abb105 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ApplicationWorksheetFunctionInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ApplicationWorksheetFunctionInspection.cs @@ -12,6 +12,47 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about late-bound WorksheetFunction calls made against the extended interface of the Application object. + /// + /// + /// + /// An early-bound, equivalent function likely exists in the object returned by the Application.WorksheetFunction property; + /// late-bound member calls will fail at run-time with error 438 if there is a typo (a typo fails to compile for an early-bound member call). + /// Late-bound worksheet functions will return a Variant/Error given invalid inputs; + /// the equivalent early-bound member calls raise a more VB-idiomatic runtime error given the same invalid inputs. + /// A Variant/Error value cannot be coerced into any other data type, be it for assignment or comparison. + /// Trying to compare or assign a Variant/Error to another data type will throw error 13 "type mismatch" at run-time. + /// Consider using the early-bound equivalent function instead. + /// + /// + /// 15 Then + /// ' won't run, error 13 "type mismatch" will be thrown when Variant/Error is compared to an Integer. + /// End If + /// End Sub + /// ]]> + /// + /// + /// 15 Then ' throws error 1004 + /// ' won't run, error 1004 is thrown when "ABC" is processed by WorksheetFunction.Sum, before it returns. + /// End If + /// End Sub + /// ]]> + /// [RequiredLibrary("Excel")] public class ApplicationWorksheetFunctionInspection : InspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ExcelMemberMayReturnNothingInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ExcelMemberMayReturnNothingInspection.cs new file mode 100644 index 0000000000..0f4808a0ca --- /dev/null +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ExcelMemberMayReturnNothingInspection.cs @@ -0,0 +1,59 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using Rubberduck.Inspections.Abstract; +using Rubberduck.Parsing.Inspections; +using Rubberduck.Parsing.Symbols; +using Rubberduck.Parsing.VBA; +using Rubberduck.Resources.Inspections; + +namespace Rubberduck.Inspections.Concrete +{ + /// Locates instances of member calls made against the result of a Range.Find/FindNext/FindPrevious method, without prior validation. + /// + /// + /// Range.Find methods return a Range object reference that refers to the cell containing the search string; + /// this object reference will be Nothing if the search didn't turn up any results, and a member call against Nothing will raise run-time error 91. + /// + /// + /// + /// + /// + /// + /// + [RequiredLibrary("Excel")] + public class ExcelMemberMayReturnNothingInspection : MemberAccessMayReturnNothingInspectionBase + { + public ExcelMemberMayReturnNothingInspection(RubberduckParserState state) : base(state) { } + + private static readonly List ExcelMembers = new List + { + "Range.Find", + "Range.FindNext", + "Range.FindPrevious" + }; + + public override List MembersUnderTest => BuiltInDeclarations + .Where(decl => decl.ProjectName.Equals("Excel") && ExcelMembers.Any(member => decl.QualifiedName.ToString().EndsWith(member))) + .ToList(); + + public override string ResultTemplate => InspectionResults.ExcelMemberMayReturnNothingInspection; + } +} diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelUdfNameIsValidCellReferenceInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ExcelUdfNameIsValidCellReferenceInspection.cs similarity index 77% rename from Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelUdfNameIsValidCellReferenceInspection.cs rename to Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ExcelUdfNameIsValidCellReferenceInspection.cs index 6d832fa758..421a0094ab 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelUdfNameIsValidCellReferenceInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ExcelUdfNameIsValidCellReferenceInspection.cs @@ -13,6 +13,26 @@ namespace Rubberduck.Inspections.Inspections.Concrete { + /// + /// Locates public User-Defined Function procedures accidentally named after a cell reference. + /// + /// + /// + /// Another good reason to avoid numeric suffixes: if the function is meant to be used as a UDF in a cell formula, + /// the worksheet cell by the same name takes precedence and gets the reference, and the function is never invoked. + /// + /// + /// + /// + /// + /// + /// [RequiredLibrary("Excel")] public class ExcelUdfNameIsValidCellReferenceInspection : InspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveSheetReferenceInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ImplicitActiveSheetReferenceInspection.cs similarity index 63% rename from Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveSheetReferenceInspection.cs rename to Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ImplicitActiveSheetReferenceInspection.cs index d8612f1718..22d07c8243 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveSheetReferenceInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ImplicitActiveSheetReferenceInspection.cs @@ -10,6 +10,34 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates unqualified Worksheet.Range/Cells/Columns/Rows member calls that implicitly refer to ActiveSheet. + /// + /// + /// + /// Implicit references to the active worksheet rarely mean to be working with *whatever worksheet is currently active*. + /// By explicitly qualifying these member calls with a specific Worksheet object, the assumptions are removed, the code + /// is more robust, and will be less likely to throw run-time error 1004 or produce unexpected results + /// when the active sheet isn't the expected one. + /// + /// + /// + /// + /// + /// + /// [RequiredLibrary("Excel")] public sealed class ImplicitActiveSheetReferenceInspection : InspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveWorkbookReferenceInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ImplicitActiveWorkbookReferenceInspection.cs similarity index 64% rename from Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveWorkbookReferenceInspection.cs rename to Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ImplicitActiveWorkbookReferenceInspection.cs index c11b8276ba..3e5df143bc 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveWorkbookReferenceInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/ImplicitActiveWorkbookReferenceInspection.cs @@ -11,6 +11,32 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates unqualified Workbook.Worksheets/Sheets/Names member calls that implicitly refer to ActiveWorkbook. + /// + /// + /// + /// Implicit references to the active workbook rarely mean to be working with *whatever workbook is currently active*. + /// By explicitly qualifying these member calls with a specific Workbook object, the assumptions are removed, the code + /// is more robust, and will be less likely to throw run-time error 1004 or produce unexpected results + /// when the active workbook isn't the expected one. + /// + /// + /// + /// + /// + /// + /// [RequiredLibrary("Excel")] public sealed class ImplicitActiveWorkbookReferenceInspection : InspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/SheetAccessedUsingStringInspection.cs similarity index 81% rename from Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs rename to Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/SheetAccessedUsingStringInspection.cs index ad5d4b75fd..5181a1c175 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/Excel/SheetAccessedUsingStringInspection.cs @@ -14,6 +14,34 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates ThisWorkbook.Worksheets and ThisWorkbook.Sheets calls that appear to be dereferencing a worksheet that is already accessible at compile-time with a global-scope identifier. + /// + /// + /// Sheet names can be changed by the user, as can a worksheet's index in ThisWorkbook.Worksheets. + /// Worksheets that exist in ThisWorkbook at compile-time are more reliably programmatically accessed using their CodeName, + /// which cannot be altered by the user without accessing the VBE and altering the VBA project. + /// + /// + /// + /// Inspection only evaluates hard-coded string literals; string-valued expressions evaluating into a sheet name are ignored. + /// + /// + /// + /// + /// + /// + /// [RequiredHost("EXCEL.EXE")] [RequiredLibrary("Excel")] public class SheetAccessedUsingStringInspection : InspectionBase diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueNotUsedInspection.cs index 7d68df38cd..1972056e3e 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueNotUsedInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueNotUsedInspection.cs @@ -15,7 +15,37 @@ namespace Rubberduck.Inspections.Concrete { - // bug: quick fix for converting to sub is exposed for interface members now + /// + /// Warns when a user function's return value is never used, at any of its call sites. + /// + /// + /// A 'Function' procedure normally means its return value to be captured and consumed by the calling code. + /// It's possible that not all call sites need the return value, but if the value is systematically discarded then this + /// means the function is side-effecting, and thus should probably be a 'Sub' procedure instead. + /// + /// + /// + /// + /// + /// + /// public sealed class FunctionReturnValueNotUsedInspection : InspectionBase { public FunctionReturnValueNotUsedInspection(RubberduckParserState state) @@ -23,8 +53,6 @@ public FunctionReturnValueNotUsedInspection(RubberduckParserState state) protected override IEnumerable DoGetInspectionResults() { - // Note: This inspection does not find dictionary calls (e.g. foo!bar) since we do not know what the - // default member is of a class. var interfaceMembers = State.DeclarationFinder.FindAllInterfaceMembers().ToList(); var interfaceImplementationMembers = State.DeclarationFinder.FindAllInterfaceImplementingMembers(); var functions = State.DeclarationFinder diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/HostSpecificExpressionInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/HostSpecificExpressionInspection.cs index 0c195b7b85..7bd480899c 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/HostSpecificExpressionInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/HostSpecificExpressionInspection.cs @@ -9,6 +9,27 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about host-evaluated square-bracketed expressions. + /// + /// + /// Host-evaluated expressions should be implementable using the host application's object model. + /// If the expression yields an object, member calls against that object are late-bound. + /// + /// + /// + /// + /// + /// + /// public sealed class HostSpecificExpressionInspection : InspectionBase { public HostSpecificExpressionInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/HungarianNotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/HungarianNotationInspection.cs index f7a8589bcc..99eaa7d81a 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/HungarianNotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/HungarianNotationInspection.cs @@ -14,6 +14,38 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Flags identifiers that use [Systems] Hungarian Notation prefixes. + /// + /// + /// Systems Hungarian (encoding data types in variable names) stemmed from a misunderstanding of what its inventor meant + /// when they described that prefixes identified the "kind" of variable in a naming scheme dubbed Apps Hungarian. + /// Modern naming conventions in all programming languages heavily discourage the use of Systems Hungarian prefixes. + /// + /// + /// + /// + /// + /// + /// public sealed class HungarianNotationInspection : InspectionBase { #region statics diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs index fcc9e3e992..5f20dda603 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs @@ -8,12 +8,37 @@ using Rubberduck.Parsing.Symbols; using Rubberduck.Resources.Inspections; using Rubberduck.Parsing.VBA; -using Rubberduck.Parsing.VBA.DeclarationCaching; using Rubberduck.Parsing.VBA.Extensions; using Rubberduck.VBEditor.SafeComWrappers; namespace Rubberduck.Inspections.Concrete { + /// + /// Flags invalid Rubberduck annotation comments. + /// + /// + /// Rubberduck is correctly parsing an annotation, but that annotation is illegal in that context. + /// + /// + /// + /// + /// + /// + /// public sealed class IllegalAnnotationInspection : InspectionBase { public IllegalAnnotationInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitByRefModifierInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitByRefModifierInspection.cs index dd732056b0..1a2bb316a3 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitByRefModifierInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitByRefModifierInspection.cs @@ -14,6 +14,27 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Highlights implicit ByRef modifiers in user code. + /// + /// + /// In modern VB (VB.NET), the implicit modifier is ByVal, as it is in most other programming languages. + /// Making the ByRef modifiers explicit can help surface potentially unexpected language defaults. + /// + /// + /// + /// + /// + /// + /// public sealed class ImplicitByRefModifierInspection : ParseTreeInspectionBase { public ImplicitByRefModifierInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAssignmentInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAssignmentInspection.cs index b9afeee310..56f872dc29 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAssignmentInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAssignmentInspection.cs @@ -13,6 +13,26 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies implicit default member calls. + /// + /// + /// Code should do what it says, and say what it does. Implicit default member calls generally do the opposite of that. + /// + /// + /// + /// + /// + /// + /// public sealed class ImplicitDefaultMemberAssignmentInspection : InspectionBase { public ImplicitDefaultMemberAssignmentInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitPublicMemberInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitPublicMemberInspection.cs index 92c4a98b72..8510d87059 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitPublicMemberInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitPublicMemberInspection.cs @@ -9,6 +9,27 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Highlights implicit Public access modifiers in user code. + /// + /// + /// In modern VB (VB.NET), the implicit access modifier is Private, as it is in most other programming languages. + /// Making the Public modifiers explicit can help surface potentially unexpected language defaults. + /// + /// + /// + /// + /// + /// + /// public sealed class ImplicitPublicMemberInspection : InspectionBase { public ImplicitPublicMemberInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitVariantReturnTypeInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitVariantReturnTypeInspection.cs index 25ff503119..02ac8bce24 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitVariantReturnTypeInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitVariantReturnTypeInspection.cs @@ -12,6 +12,26 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about 'Function' and 'Property Get' procedures that don't have an explicit return type. + /// + /// + /// All functions return something, whether a type is specified or not. The implicit default is 'Variant'. + /// + /// + /// + /// + /// + /// + /// public sealed class ImplicitVariantReturnTypeInspection : InspectionBase { public ImplicitVariantReturnTypeInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IntegerDataTypeInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IntegerDataTypeInspection.cs index f166fe4a0e..6d835ef0cb 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IntegerDataTypeInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IntegerDataTypeInspection.cs @@ -12,6 +12,29 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies obsolete 16-bit integer variables. + /// + /// + /// Modern processors are optimized for processing 32-bit integers; internally, a 16-bit integer is still stored as a 32-bit value. + /// Unless code is interacting with APIs that require a 16-bit integer, a Long (32-bit integer) should be used instead. + /// + /// + /// + /// + /// + /// + /// public sealed class IntegerDataTypeInspection : InspectionBase { public IntegerDataTypeInspection(RubberduckParserState state) : base(state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingOnInappropriateArgumentInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingOnInappropriateArgumentInspection.cs index 8cb3f80b52..2f852255a9 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingOnInappropriateArgumentInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingOnInappropriateArgumentInspection.cs @@ -10,6 +10,29 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies uses of 'IsMissing' involving non-variant, non-optional, or array parameters. + /// + /// + /// 'IsMissing' only returns True when an optional Variant parameter was not supplied as an argument. + /// This inspection flags uses that attempt to use 'IsMissing' for other purposes, resulting in conditions that are always False. + /// + /// + /// + /// + /// + /// + /// public class IsMissingOnInappropriateArgumentInspection : IsMissingInspectionBase { public IsMissingOnInappropriateArgumentInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingWithNonArgumentParameterInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingWithNonArgumentParameterInspection.cs index cf0def6056..edf2357496 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingWithNonArgumentParameterInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingWithNonArgumentParameterInspection.cs @@ -9,6 +9,30 @@ namespace Rubberduck.Inspections.Inspections.Concrete { + /// + /// Identifies uses of 'IsMissing' involving a non-parameter argument. + /// + /// + /// 'IsMissing' only returns True when an optional Variant parameter was not supplied as an argument. + /// This inspection flags uses that attempt to use 'IsMissing' for other purposes, resulting in conditions that are always False. + /// + /// + /// + /// + /// + /// + /// public class IsMissingWithNonArgumentParameterInspection : IsMissingInspectionBase { public IsMissingWithNonArgumentParameterInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/LineLabelNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/LineLabelNotUsedInspection.cs index 9f8e5e86e0..212997afac 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/LineLabelNotUsedInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/LineLabelNotUsedInspection.cs @@ -14,6 +14,35 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies line labels that are never referenced, and therefore superfluous. + /// + /// + /// Line labels are useful for GoTo, GoSub, Resume, and On Error statements; but the intent of a line label + /// can be confusing if it isn't referenced by any such instruction. + /// + /// + /// + /// + /// + /// + /// public sealed class LineLabelNotUsedInspection : InspectionBase { public LineLabelNotUsedInspection(RubberduckParserState state) : base(state) { } diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MemberAccessMayReturnNothingInspection/ExcelMemberMayReturnNothingInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MemberAccessMayReturnNothingInspection/ExcelMemberMayReturnNothingInspection.cs deleted file mode 100644 index 7d422f5abc..0000000000 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MemberAccessMayReturnNothingInspection/ExcelMemberMayReturnNothingInspection.cs +++ /dev/null @@ -1,30 +0,0 @@ -using System; -using System.Collections.Generic; -using System.Linq; -using Rubberduck.Inspections.Abstract; -using Rubberduck.Parsing.Inspections; -using Rubberduck.Parsing.Symbols; -using Rubberduck.Parsing.VBA; -using Rubberduck.Resources.Inspections; - -namespace Rubberduck.Inspections.Concrete -{ - [RequiredLibrary("Excel")] - public class ExcelMemberMayReturnNothingInspection : MemberAccessMayReturnNothingInspectionBase - { - public ExcelMemberMayReturnNothingInspection(RubberduckParserState state) : base(state) { } - - private static readonly List ExcelMembers = new List - { - "Range.Find", - "Range.FindNext", - "Range.FindPrevious" - }; - - public override List MembersUnderTest => BuiltInDeclarations - .Where(decl => decl.ProjectName.Equals("Excel") && ExcelMembers.Any(member => decl.QualifiedName.ToString().EndsWith(member))) - .ToList(); - - public override string ResultTemplate => InspectionResults.ExcelMemberMayReturnNothingInspection; - } -} diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MemberNotOnInterfaceInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MemberNotOnInterfaceInspection.cs index a193f81b02..244783bf0e 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MemberNotOnInterfaceInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MemberNotOnInterfaceInspection.cs @@ -11,6 +11,32 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about member calls against an extensible interface, that cannot be validated at compile-time. + /// + /// + /// Extensible COM types can have members attached at run-time; VBA cannot bind these member calls at compile-time. + /// If there is an early-bound alternative way to achieve the same result, it should be preferred. + /// + /// + /// + /// + /// + /// + /// public sealed class MemberNotOnInterfaceInspection : InspectionBase { public MemberNotOnInterfaceInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs index 313585f8c0..1dcb73f1b7 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs @@ -14,6 +14,28 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about a malformed Rubberduck annotation that is missing an argument. + /// + /// + /// Some annotations require arguments; if the argument isn't specified, the annotation is nothing more than an obscure comment. + /// + /// + /// + /// + /// + /// + /// public sealed class MissingAnnotationArgumentInspection : ParseTreeInspectionBase { public MissingAnnotationArgumentInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs index eb141ed7fc..6d436319cf 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs @@ -13,6 +13,30 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Indicates that a Rubberduck annotation is documenting the presence of a VB attribute that is actually missing. + /// + /// + /// Rubberduck annotations mean to document the presence of hidden VB attributes; this inspection flags annotations that + /// do not have a corresponding VB attribute. + /// + /// + /// + /// + /// + /// + /// [CannotAnnotate] public sealed class MissingAttributeInspection : InspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs index 864bde2731..ef8df68826 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs @@ -13,6 +13,30 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Indicates that a hidden VB attribute is present for a member, but no Rubberduck annotation is documenting it. + /// + /// + /// Rubberduck annotations mean to document the presence of hidden VB attributes; this inspection flags members that + /// do not have a Rubberduck annotation corresponding to the hidden VB attribute. + /// + /// + /// + /// + /// + /// + /// public sealed class MissingMemberAnnotationInspection : InspectionBase { public MissingMemberAnnotationInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs index 320c50f612..60cb6c6d3e 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs @@ -14,6 +14,28 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Indicates that a hidden VB attribute is present for a module, but no Rubberduck annotation is documenting it. + /// + /// + /// Rubberduck annotations mean to document the presence of hidden VB attributes; this inspection flags modules that + /// do not have a Rubberduck annotation corresponding to the hidden VB attribute. + /// + /// + /// + /// + /// + /// + /// public sealed class MissingModuleAnnotationInspection : InspectionBase { public MissingModuleAnnotationInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleScopeDimKeywordInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleScopeDimKeywordInspection.cs index 7f264c4865..af954b2b2c 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleScopeDimKeywordInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleScopeDimKeywordInspection.cs @@ -14,6 +14,27 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about module-level declarations made using the 'Dim' keyword. + /// + /// + /// Private module variables should be declared using the 'Private' keyword. While 'Dim' is also legal, it should preferably be + /// restricted to declarations of procedure-scoped local variables, for consistency, since public module variables are declared with the 'Public' keyword. + /// + /// + /// + /// + /// + /// + /// public sealed class ModuleScopeDimKeywordInspection : ParseTreeInspectionBase { public ModuleScopeDimKeywordInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs index dd6c0bfd8b..9d8dcdfb6f 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs @@ -10,6 +10,26 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Indicates that a user module is missing a @Folder Rubberduck annotation. + /// + /// + /// Modules without a custom @Folder annotation will be grouped under the default folder in the Code Explorer toolwindow. + /// By specifying a custom @Folder annotation, modules can be organized by functionality rather than simply listed. + /// + /// + /// + /// + /// + /// + /// public sealed class ModuleWithoutFolderInspection : InspectionBase { public ModuleWithoutFolderInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MoveFieldCloserToUsageInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MoveFieldCloserToUsageInspection.cs index fa3cdf55c5..3e34d2555e 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MoveFieldCloserToUsageInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MoveFieldCloserToUsageInspection.cs @@ -10,6 +10,35 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates module-level fields that can be moved to a smaller scope. + /// + /// + /// Module-level variables that are only used in a single procedure can often be declared in that procedure's scope. + /// Declaring variables closer to where they are used generally makes the code easier to follow. + /// + /// + /// + /// + /// + /// + /// public sealed class MoveFieldCloserToUsageInspection : InspectionBase { public MoveFieldCloserToUsageInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MultilineParameterInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MultilineParameterInspection.cs index 15fba25fa5..024c189f77 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MultilineParameterInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MultilineParameterInspection.cs @@ -14,6 +14,28 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Flags parameters declared across multiple physical lines of code. + /// + /// + /// When splitting a long list of parameters across multiple lines, care should be taken to avoid splitting a parameter declaration in two. + /// + /// + /// + /// + /// + /// + /// public sealed class MultilineParameterInspection : ParseTreeInspectionBase { public MultilineParameterInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MultipleDeclarationsInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MultipleDeclarationsInspection.cs index cdb394f379..8e0f0e0fac 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MultipleDeclarationsInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MultipleDeclarationsInspection.cs @@ -14,6 +14,23 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Flags declaration statements spanning multiple physical lines of code. + /// + /// + /// Declaration statements should generally declare a single variable. + /// + /// + /// + /// + /// + /// + /// public sealed class MultipleDeclarationsInspection : ParseTreeInspectionBase { public MultipleDeclarationsInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/NonReturningFunctionInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/NonReturningFunctionInspection.cs index 9411104ad5..d0b575d52f 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/NonReturningFunctionInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/NonReturningFunctionInspection.cs @@ -11,6 +11,30 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about 'Function' and 'Property Get' procedures whose return value is not assigned. + /// + /// + /// Both 'Function' and 'Property Get' accessors should always return something. Omitting the return assignment is likely a bug. + /// + /// + /// + /// + /// + /// + /// public sealed class NonReturningFunctionInspection : InspectionBase { public NonReturningFunctionInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectVariableNotSetInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectVariableNotSetInspection.cs index 90ee5be8c8..9d8daad051 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectVariableNotSetInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectVariableNotSetInspection.cs @@ -10,6 +10,31 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about assignments that appear to be assigning an object reference without the 'Set' keyword. + /// + /// + /// Omitting the 'Set' keyword will Let-coerce the right-hand side (RHS) of the assignment expression. If the RHS is an object variable, + /// then the assignment is implicitly assigning to that object's default member, which may raise run-time error 91 at run-time. + /// + /// + /// + /// + /// + /// + /// public sealed class ObjectVariableNotSetInspection : InspectionBase { public ObjectVariableNotSetInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallStatementInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallStatementInspection.cs index ee4bfeea1f..2f67e83484 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallStatementInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallStatementInspection.cs @@ -14,6 +14,34 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates explicit 'Call' statements. + /// + /// + /// The 'Call' keyword is obsolete and redundant, since call statements are legal and generally more consistent without it. + /// + /// + /// + /// + /// + /// + /// public sealed class ObsoleteCallStatementInspection : ParseTreeInspectionBase { public ObsoleteCallStatementInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallingConventionInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallingConventionInspection.cs index 74d448284b..3313a48ca1 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallingConventionInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallingConventionInspection.cs @@ -13,6 +13,23 @@ namespace Rubberduck.Inspections.Inspections.Concrete { + /// + /// Warns about 'Declare' statements that are using the obsolete/unsupported 'CDecl' calling convention on Windows. + /// + /// + /// The CDecl calling convention is only implemented in VBA for Mac; if Rubberduck can see it (Rubberduck only runs on Windows), + /// then the declaration is using an unsupported (no-op) calling convention on Windows. + /// + /// + /// + /// + /// + /// + /// public sealed class ObsoleteCallingConventionInspection : ParseTreeInspectionBase { public ObsoleteCallingConventionInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCommentSyntaxInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCommentSyntaxInspection.cs index 4fce4542ec..5b9ceb9dca 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCommentSyntaxInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCommentSyntaxInspection.cs @@ -13,6 +13,26 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates legacy 'Rem' comments. + /// + /// + /// Modern VB comments use a single quote character (') to denote the beginning of a comment: the legacy 'Rem' syntax is obsolete. + /// + /// + /// + /// + /// + /// + /// public sealed class ObsoleteCommentSyntaxInspection : ParseTreeInspectionBase { public ObsoleteCommentSyntaxInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteErrorSyntaxInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteErrorSyntaxInspection.cs index 014d6dca4c..cd3234d4b0 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteErrorSyntaxInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteErrorSyntaxInspection.cs @@ -13,6 +13,26 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates legacy 'Error' statements. + /// + /// + /// The legacy syntax is obsolete; prefer 'Err.Raise' instead. + /// + /// + /// + /// + /// + /// + /// public sealed class ObsoleteErrorSyntaxInspection : ParseTreeInspectionBase { public ObsoleteErrorSyntaxInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteGlobalInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteGlobalInspection.cs index 56446a4c63..18911edb84 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteGlobalInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteGlobalInspection.cs @@ -10,6 +10,24 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates legacy 'Global' declaration statements. + /// + /// + /// The legacy syntax is obsolete; use the 'Public' keyword instead. + /// + /// + /// + /// + /// + /// + /// public sealed class ObsoleteGlobalInspection : InspectionBase { public ObsoleteGlobalInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteLetStatementInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteLetStatementInspection.cs index 771c63772f..c491bcf1ab 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteLetStatementInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteLetStatementInspection.cs @@ -13,6 +13,28 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates explicit 'Let' assignments. + /// + /// + /// The legacy syntax is obsolete/redundant; prefer implicit Let-coercion instead. + /// + /// + /// + /// + /// + /// + /// public sealed class ObsoleteLetStatementInspection : ParseTreeInspectionBase { public ObsoleteLetStatementInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs index 1ab1e7552a..8201003b23 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs @@ -10,6 +10,44 @@ namespace Rubberduck.Inspections.Inspections.Concrete { + /// + /// Flags usages of members marked as obsolete with an @Obsolete("justification") Rubberduck annotation. + /// + /// + /// Marking members as obsolete can help refactoring a legacy code base. This inspection is a tool that makes it easy to locate obsolete member calls. + /// + /// + /// + /// + /// + /// + /// public sealed class ObsoleteMemberUsageInspection : InspectionBase { public ObsoleteMemberUsageInspection(RubberduckParserState state) : base(state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteTypeHintInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteTypeHintInspection.cs index f766d46771..ff03445a31 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteTypeHintInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteTypeHintInspection.cs @@ -8,6 +8,28 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Flags declarations where a type hint is used in place of an 'As' clause. + /// + /// + /// Type hints were made obsolete when declaration syntax introduced the 'As' keyword. Prefer explicit type names over type hint symbols. + /// + /// + /// + /// + /// + /// + /// public sealed class ObsoleteTypeHintInspection : InspectionBase { public ObsoleteTypeHintInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteWhileWendStatementInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteWhileWendStatementInspection.cs new file mode 100644 index 0000000000..e600410a29 --- /dev/null +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteWhileWendStatementInspection.cs @@ -0,0 +1,78 @@ +using Rubberduck.Inspections.Abstract; +using System.Collections.Generic; +using System.Linq; +using Antlr4.Runtime; +using Rubberduck.Inspections.Inspections.Extensions; +using Rubberduck.Inspections.Results; +using Rubberduck.Parsing; +using Rubberduck.Parsing.Grammar; +using Rubberduck.Parsing.Inspections.Abstract; +using Rubberduck.Parsing.VBA; +using Rubberduck.Resources.Inspections; +using Rubberduck.VBEditor; + +namespace Rubberduck.CodeAnalysis.Inspections.Concrete +{ + /// + /// Flags 'While...Wend' loops as obsolete. + /// + /// + /// 'While...Wend' loops were made obsolete when 'Do While...Loop' statements were introduced. + /// 'While...Wend' loops cannot be exited early without a GoTo jump; 'Do...Loop' statements can be conditionally exited with 'Exit Do'. + /// + /// + /// + /// + /// + /// + /// + public sealed class ObsoleteWhileWendStatementInspection : ParseTreeInspectionBase + { + public ObsoleteWhileWendStatementInspection(RubberduckParserState state) + : base(state) + { + Listener = new ObsoleteWhileWendStatementListener(); + } + + public override IInspectionListener Listener { get; } + + protected override IEnumerable DoGetInspectionResults() + { + return Listener.Contexts.Where(context => + !context.IsIgnoringInspectionResultFor(State.DeclarationFinder, AnnotationName)) + .Select(context => new QualifiedContextInspectionResult(this, InspectionResults.ObsoleteWhileWendStatementInspection, context)); + } + + public class ObsoleteWhileWendStatementListener : VBAParserBaseListener, IInspectionListener + { + private readonly List> _contexts = + new List>(); + + public IReadOnlyList> Contexts => _contexts; + + public QualifiedModuleName CurrentModuleName { get; set; } + + public void ClearContexts() + { + _contexts.Clear(); + } + + public override void ExitWhileWendStmt(VBAParser.WhileWendStmtContext context) + { + _contexts.Add(new QualifiedContext(CurrentModuleName, context)); + } + } + } +} \ No newline at end of file diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/OnLocalErrorInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/OnLocalErrorInspection.cs index 3368d09d22..e9e4547817 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/OnLocalErrorInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/OnLocalErrorInspection.cs @@ -14,6 +14,34 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Flags obsolete 'On Local Error' statements. + /// + /// + /// All errors are "local" - the keyword is redundant/confusing and should be removed. + /// + /// + /// + /// + /// + /// + /// public sealed class OnLocalErrorInspection : ParseTreeInspectionBase { public OnLocalErrorInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionBaseInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionBaseInspection.cs index f1c620e12a..b5a9565c43 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionBaseInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionBaseInspection.cs @@ -13,6 +13,35 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Flags modules that specify Option Base 1. + /// + /// + /// Implicit array lower bound is 0 by default, and Option Base 1 makes it 1. While compelling in a 1-based environment like the Excel object model, + /// having an implicit lower bound of 1 for implicitly-sized user arrays does not change the fact that arrays are always better off with explicit boundaries. + /// Because 0 is always the lower array bound in many other programming languages, this option may trip a reader/maintainer with a different background. + /// + /// + /// + /// + /// + /// + /// public sealed class OptionBaseInspection : ParseTreeInspectionBase { public OptionBaseInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionExplicitInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionExplicitInspection.cs index 81768a4665..dff829224f 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionExplicitInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionExplicitInspection.cs @@ -14,6 +14,31 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Flags modules that omit Option Explicit. + /// + /// + /// This option makes variable declarations mandatory. Without it, a typo gets compiled as a new on-the-spot Variant/Empty variable with a new name. + /// Omitting this option amounts to refusing the little help the VBE can provide with compile-time validation. + /// + /// + /// + /// + /// + /// + /// public sealed class OptionExplicitInspection : ParseTreeInspectionBase { public OptionExplicitInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterCanBeByValInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterCanBeByValInspection.cs index 847a68ca3d..eab279332c 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterCanBeByValInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterCanBeByValInspection.cs @@ -16,6 +16,30 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Flags parameters that are passed by reference (ByRef), but could be passed by value (ByVal). + /// + /// + /// Explicitly specifying a ByVal modifier on a parameter makes the intent explicit: this parameter is not meant to be assigned. In contrast, + /// a parameter that is passed by reference (implicitly, or explicitly ByRef) makes it ambiguous from the calling code's standpoint, whether the + /// procedure might re-assign these ByRef values and introduce a bug. + /// + /// + /// + /// + /// + /// + /// public sealed class ParameterCanBeByValInspection : InspectionBase { public ParameterCanBeByValInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterNotUsedInspection.cs index 39a0d52a07..c4140b7759 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterNotUsedInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterNotUsedInspection.cs @@ -11,6 +11,33 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies parameter declarations that are not used. + /// + /// + /// Declarations that are not used anywhere should probably be removed. + /// + /// + /// Not all unused parameters can/should be removed: ignore any inspection results for + /// event handler procedures and interface members that Rubberduck isn't recognizing as such. + /// + /// + /// + /// + /// + /// + /// public sealed class ParameterNotUsedInspection : InspectionBase { public ParameterNotUsedInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs index 7e2713269f..d2f9491355 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs @@ -15,6 +15,32 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about 'Sub' procedures that could be refactored into a 'Function'. + /// + /// + /// Idiomatic VB code uses 'Function' procedures to return a single value. If the procedure isn't side-effecting, consider writing is as a + /// 'Function' rather than a 'Sub' the returns a result through a 'ByRef' parameter. + /// + /// + /// + /// + /// + /// + /// public sealed class ProcedureCanBeWrittenAsFunctionInspection : ParseTreeInspectionBase { public ProcedureCanBeWrittenAsFunctionInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureNotUsedInspection.cs index 3b4f32fcd7..ecbc54131e 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureNotUsedInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureNotUsedInspection.cs @@ -11,6 +11,37 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates procedures that are never invoked from user code. + /// + /// + /// Unused procedures are dead code that should probably be removed. Note, a procedure may be effectively "not used" in code, but attached to some + /// Shape object in the host document: in such cases the inspection result should be ignored. An event handler procedure that isn't being + /// resolved as such, may also wrongly trigger this inspection. + /// + /// + /// Not all unused procedures can/should be removed: ignore any inspection results for + /// event handler procedures and interface members that Rubberduck isn't recognizing as such. + /// + /// + /// + /// + /// + /// + /// public sealed class ProcedureNotUsedInspection : InspectionBase { public ProcedureNotUsedInspection(RubberduckParserState state) : base(state) { } diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantByRefModifierInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantByRefModifierInspection.cs index 60712b0e30..455b1088fc 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantByRefModifierInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantByRefModifierInspection.cs @@ -14,6 +14,32 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies redundant ByRef modifiers. + /// + /// + /// Out of convention or preference, explicit ByRef modifiers could be considered redundant since they are the implicit default. + /// This inspection can ensure the consistency of the convention. + /// + /// + /// + /// + /// + /// + /// public sealed class RedundantByRefModifierInspection : ParseTreeInspectionBase { public RedundantByRefModifierInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantOptionInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantOptionInspection.cs index 30b77d4537..a3887eea32 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantOptionInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantOptionInspection.cs @@ -13,6 +13,31 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies redundant module options that are set to their implicit default. + /// + /// + /// Module options that are redundant can be safely removed. Disable this inspection if your convention is to explicitly specify them; a future + /// inspection may be used to enforce consistently explicit module options. + /// + /// + /// + /// + /// + /// + /// public sealed class RedundantOptionInspection : ParseTreeInspectionBase { public RedundantOptionInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/SelfAssignedDeclarationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/SelfAssignedDeclarationInspection.cs index d8c1a70ffb..b2c5f399cf 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/SelfAssignedDeclarationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/SelfAssignedDeclarationInspection.cs @@ -11,6 +11,38 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies auto-assigned object declarations. + /// + /// + /// Auto-assigned objects are automatically re-created as soon as they are referenced. It is therefore impossible to set one such reference + /// to 'Nothing' and then verifying whether the object 'Is Nothing': it will never be. This behavior is potentially confusing and bug-prone. + /// + /// + /// + /// + /// + /// + /// public sealed class SelfAssignedDeclarationInspection : InspectionBase { public SelfAssignedDeclarationInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ShadowedDeclarationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ShadowedDeclarationInspection.cs index 517045e911..ea3b8bce2a 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ShadowedDeclarationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ShadowedDeclarationInspection.cs @@ -12,6 +12,33 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Identifies identifiers that hide/"shadow" other identifiers otherwise accessible in that scope. + /// + /// + /// Global namespace contains a number of perfectly legal identifier names that user code can use. But using these names in user code + /// effectively "hides" the global ones. In general, avoid shadowing global-scope identifiers if possible. + /// + /// + /// + /// + /// + /// + /// public sealed class ShadowedDeclarationInspection : InspectionBase { private enum DeclarationSite diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/StepIsNotSpecifiedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/StepIsNotSpecifiedInspection.cs index df0b2ffa80..cf0aeec51e 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/StepIsNotSpecifiedInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/StepIsNotSpecifiedInspection.cs @@ -15,6 +15,33 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates 'For' loops where the 'Step' token is omitted. + /// + /// + /// Out of convention or preference, explicit 'Step' specifiers could be considered mandatory; + /// this inspection can ensure the consistency of the convention. + /// + /// + /// + /// + /// + /// + /// public sealed class StepIsNotSpecifiedInspection : ParseTreeInspectionBase { public StepIsNotSpecifiedInspection(RubberduckParserState state) : base(state) { } diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/StepOneIsRedundantInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/StepOneIsRedundantInspection.cs index b84b86a525..8081d944ec 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/StepOneIsRedundantInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/StepOneIsRedundantInspection.cs @@ -15,6 +15,33 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates 'For' loops where the 'Step' token is specified with the default increment value (1). + /// + /// + /// Out of convention or preference, explicit 'Step 1' specifiers could be considered redundant; + /// this inspection can ensure the consistency of the convention. + /// + /// + /// + /// + /// + /// + /// public sealed class StepOneIsRedundantInspection : ParseTreeInspectionBase { public StepOneIsRedundantInspection(RubberduckParserState state) : base(state) { } diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/StopKeywordInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/StopKeywordInspection.cs index aea982d7f2..ecbe9e9b1b 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/StopKeywordInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/StopKeywordInspection.cs @@ -14,6 +14,30 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Locates 'Stop' instructions in user code. + /// + /// + /// While a great debugging tool, 'Stop' instructions should not be reachable in production code; this inspection makes it easy to locate them all. + /// + /// + /// + /// + /// + /// + /// public sealed class StopKeywordInspection : ParseTreeInspectionBase { public StopKeywordInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/KeywordsUsedAsMemberInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/KeywordsUsedAsMemberInspection.cs index 9ca8b126a9..b6c85cde67 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/KeywordsUsedAsMemberInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/KeywordsUsedAsMemberInspection.cs @@ -10,6 +10,15 @@ namespace Rubberduck.Inspections.Inspections.Concrete.ThunderCode { + /// + /// A ThunderCode inspection that locates instances of various keywords and reserved identifiers used as Type or Enum member names. + /// + /// + /// This inpection is flagging code we dubbed "ThunderCode", + /// code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + /// While perfectly legal as Type or Enum member names, these identifiers should be avoided: + /// they need to be square-bracketed everywhere they are used. + /// public class KeywordsUsedAsMemberInspection : InspectionBase { public KeywordsUsedAsMemberInspection(RubberduckParserState state) : base(state) { } @@ -30,7 +39,7 @@ protected override IEnumerable DoGetInspectionResults() } // MS-VBAL 3.3.5.2 Reserved Identifiers and IDENTIFIER - private static IEnumerable ReservedKeywords = new [] + private static readonly IEnumerable ReservedKeywords = new [] { /* Statement-keyword = "Call" / "Case" /"Close" / "Const"/ "Declare" / "DefBool" / "DefByte" / @@ -50,19 +59,19 @@ protected override IEnumerable DoGetInspectionResults() Tokens.Close, Tokens.Const, Tokens.Declare, - "DefBool", - "DefByte", - "DefCur", - "DefDate", - "DefDbl", - "DefInt", - "DefLng", - "DefLngLng", - "DefLngPtr", - "DefObj", - "DefSng", - "DefStr", - "DefVar", + Tokens.DefBool, + Tokens.DefByte, + Tokens.DefCur, + Tokens.DefDate, + Tokens.DefDbl, + Tokens.DefInt, + Tokens.DefLng, + Tokens.DefLngLng, + Tokens.DefLngPtr, + Tokens.DefObj, + Tokens.DefSng, + Tokens.DefStr, + Tokens.DefVar, Tokens.Dim, Tokens.Do, Tokens.Else, @@ -70,8 +79,8 @@ protected override IEnumerable DoGetInspectionResults() Tokens.End, "EndIf", Tokens.Enum, - "Erase", - "Event", + Tokens.Erase, + Tokens.Event, Tokens.Exit, Tokens.For, Tokens.Friend, @@ -84,9 +93,9 @@ protected override IEnumerable DoGetInspectionResults() Tokens.Implements, Tokens.Input, Tokens.Let, - "Lock", + Tokens.Lock, Tokens.Loop, - "LSet", + Tokens.LSet, Tokens.Next, Tokens.On, Tokens.Open, @@ -95,19 +104,19 @@ protected override IEnumerable DoGetInspectionResults() Tokens.Private, Tokens.Public, Tokens.Put, - "RaiseEvent", + Tokens.RaiseEvent, Tokens.ReDim, Tokens.Resume, Tokens.Return, - "RSet", - "Seek", + Tokens.RSet, + Tokens.Seek, Tokens.Select, Tokens.Set, Tokens.Static, Tokens.Stop, Tokens.Sub, Tokens.Type, - "Unlock", + Tokens.Unlock, Tokens.Wend, Tokens.While, Tokens.With, @@ -127,9 +136,9 @@ protected override IEnumerable DoGetInspectionResults() Tokens.Each, Tokens.In, Tokens.New, - "Shared", + Tokens.Shared, Tokens.Until, - "WithEvents", + Tokens.WithEvents, Tokens.Optional, Tokens.ParamArray, Tokens.Preserve, diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/LineContinuationBetweenKeywordsInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/LineContinuationBetweenKeywordsInspection.cs index 4cf4ea4de9..a5b071d1af 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/LineContinuationBetweenKeywordsInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/LineContinuationBetweenKeywordsInspection.cs @@ -14,10 +14,17 @@ namespace Rubberduck.Inspections.Inspections.Concrete.ThunderCode { /// - /// Note that the inspection only checks a subset of possible "evil" line continatuions - /// for both simplicity and performance reasons. Exahustive inspection would likely take - /// too much effort. + /// A ThunderCode inspection that locates certain specific instances of line continuations in places we'd never think to put them. /// + /// + /// This inpection is flagging code we dubbed "ThunderCode", + /// code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + /// While perfectly legal, these line continuations serve no purpose and should be removed. + /// + /// + /// Note that the inspection only checks a subset of possible "evil" line continatuions + /// for both simplicity and performance reasons. Exhaustive inspection would likely take too much effort. + /// public class LineContinuationBetweenKeywordsInspection : ParseTreeInspectionBase { public LineContinuationBetweenKeywordsInspection(RubberduckParserState state) : base(state) @@ -28,10 +35,7 @@ public LineContinuationBetweenKeywordsInspection(RubberduckParserState state) : protected override IEnumerable DoGetInspectionResults() { return Listener.Contexts.Select(c => new QualifiedContextInspectionResult( - this, - InspectionResults.LineContinuationBetweenKeywordsInspection. - ThunderCodeFormat(), - c)); + this, InspectionResults.LineContinuationBetweenKeywordsInspection.ThunderCodeFormat(), c)); } public override IInspectionListener Listener { get; } @@ -42,10 +46,7 @@ public class LineContinuationBetweenKeywordsListener : VBAParserBaseListener, II public IReadOnlyList> Contexts => _contexts; - public void ClearContexts() - { - _contexts.Clear(); - } + public void ClearContexts() => _contexts.Clear(); public QualifiedModuleName CurrentModuleName { get; set; } diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NegativeLineNumberInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NegativeLineNumberInspection.cs index 854459bb06..b5e5b93b90 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NegativeLineNumberInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NegativeLineNumberInspection.cs @@ -13,6 +13,14 @@ namespace Rubberduck.Inspections.Inspections.Concrete.ThunderCode { + /// + /// A ThunderCode inspection that locates negative line numbers. + /// + /// + /// This inpection is flagging code we dubbed "ThunderCode", + /// code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + /// The VBE does allow rather strange and unbelievable things to happen. + /// public class NegativeLineNumberInspection : ParseTreeInspectionBase { public NegativeLineNumberInspection(RubberduckParserState state) : base(state) @@ -23,11 +31,7 @@ public NegativeLineNumberInspection(RubberduckParserState state) : base(state) protected override IEnumerable DoGetInspectionResults() { return Listener.Contexts.Select(c => new QualifiedContextInspectionResult( - this, - - InspectionResults.NegativeLineNumberInspection. - ThunderCodeFormat(), - c)); + this, InspectionResults.NegativeLineNumberInspection.ThunderCodeFormat(), c)); } public override IInspectionListener Listener { get; } @@ -38,10 +42,7 @@ public class NegativeLineNumberKeywordsListener : VBAParserBaseListener, IInspec public IReadOnlyList> Contexts => _contexts; - public void ClearContexts() - { - _contexts.Clear(); - } + public void ClearContexts() => _contexts.Clear(); public QualifiedModuleName CurrentModuleName { get; set; } diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NonBreakingSpaceIdentifierInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NonBreakingSpaceIdentifierInspection.cs index a18437308d..db1658144b 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NonBreakingSpaceIdentifierInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NonBreakingSpaceIdentifierInspection.cs @@ -8,6 +8,14 @@ namespace Rubberduck.Inspections.Inspections.Concrete.ThunderCode { + /// + /// A ThunderCode inspection that locates non-breaking spaces hidden in identifier names. + /// + /// + /// This inpection is flagging code we dubbed "ThunderCode", + /// code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + /// This inspection may accidentally reveal non-breaking spaces in code copied and pasted from a website. + /// public class NonBreakingSpaceIdentifierInspection : InspectionBase { private const string Nbsp = "\u00A0"; @@ -19,10 +27,7 @@ protected override IEnumerable DoGetInspectionResults() return State.DeclarationFinder.AllUserDeclarations .Where(d => d.IdentifierName.Contains(Nbsp)) .Select(d => new DeclarationInspectionResult( - this, - InspectionResults.NonBreakingSpaceIdentifierInspection. - ThunderCodeFormat(d.IdentifierName), - d)); + this, InspectionResults.NonBreakingSpaceIdentifierInspection.ThunderCodeFormat(d.IdentifierName), d)); } } } diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/OnErrorGoToMinusOneInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/OnErrorGoToMinusOneInspection.cs index cecaacaa5e..08d930eb41 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/OnErrorGoToMinusOneInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/OnErrorGoToMinusOneInspection.cs @@ -13,6 +13,14 @@ namespace Rubberduck.Inspections.Inspections.Concrete.ThunderCode { + /// + /// A ThunderCode inspection that locates instances of 'On Error GoTo -1' statements. + /// + /// + /// This inpection is flagging code we dubbed "ThunderCode", + /// code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + /// 'On Error GoTo -1' is poorly documented and uselessly complicates error handling. + /// public class OnErrorGoToMinusOneInspection : ParseTreeInspectionBase { public OnErrorGoToMinusOneInspection(RubberduckParserState state) : base(state) @@ -23,11 +31,7 @@ public OnErrorGoToMinusOneInspection(RubberduckParserState state) : base(state) protected override IEnumerable DoGetInspectionResults() { return Listener.Contexts.Select(c => new QualifiedContextInspectionResult( - this, - - InspectionResults.OnErrorGoToMinusOneInspection. - ThunderCodeFormat(), - c)); + this, InspectionResults.OnErrorGoToMinusOneInspection.ThunderCodeFormat(), c)); } public override IInspectionListener Listener { get; } @@ -38,10 +42,7 @@ public class OnErrorGoToMinusOneListener : VBAParserBaseListener, IInspectionLis public IReadOnlyList> Contexts => _contexts; - public void ClearContexts() - { - _contexts.Clear(); - } + public void ClearContexts() => _contexts.Clear(); public QualifiedModuleName CurrentModuleName { get; set; } diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs index ce7bd81f51..9189ee81c6 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs @@ -14,6 +14,33 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns when a variable is referenced prior to being assigned. + /// + /// + /// An uninitialized variable is being read, but since it's never assigned, the only value ever read would be the data type's default initial value. + /// Reading a variable that was never written to in any code path (especially if Option Explicit isn't specified), is likely to be a bug. + /// + /// + /// This inspection may produce false positives when the variable is an array, or if it's passed by reference (ByRef) to a procedure that assigns it. + /// + /// + /// + /// + /// + /// + /// [SuppressMessage("ReSharper", "LoopCanBeConvertedToQuery")] public sealed class UnassignedVariableUsageInspection : InspectionBase { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UndeclaredVariableInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UndeclaredVariableInspection.cs index 30834a8ecd..742b6916b8 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UndeclaredVariableInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UndeclaredVariableInspection.cs @@ -10,6 +10,29 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about implicit local variables that are used but never declared. + /// + /// + /// If this code compiles, then Option Explicit is omitted and compile-time validation is easily forfeited, even accidentally (e.g. typos). + /// + /// + /// + /// + /// + /// + /// public sealed class UndeclaredVariableInspection : InspectionBase { public UndeclaredVariableInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnderscoreInPublicClassModuleMemberInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnderscoreInPublicClassModuleMemberInspection.cs index 052f3c3efb..9818cb2b72 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnderscoreInPublicClassModuleMemberInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnderscoreInPublicClassModuleMemberInspection.cs @@ -8,6 +8,29 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about public class members with an underscore in their names. + /// + /// + /// The public interface of any class module can be implemented by any other class module; if the public interface + /// contains names with underscores, other classes cannot implement it - the code will not compile. Avoid underscores; prefer PascalCase names. + /// + /// + /// + /// + /// + /// + /// public sealed class UnderscoreInPublicClassModuleMemberInspection : InspectionBase { public UnderscoreInPublicClassModuleMemberInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnhandledOnErrorResumeNextInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnhandledOnErrorResumeNextInspection.cs index 5a68c85a81..a61bd97598 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnhandledOnErrorResumeNextInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnhandledOnErrorResumeNextInspection.cs @@ -14,6 +14,31 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Finds instances of 'On Error Resume Next' that don't have a corresponding 'On Error GoTo 0' to restore error handling. + /// + /// + /// 'On Error Resume Next' should be constrained to a limited number of instructions, otherwise it supresses error handling + /// for the rest of the procedure; 'On Error GoTo 0' reinstates error handling. + /// This inspection helps treating 'Resume Next' and 'GoTo 0' as a code block (similar to 'With...End With'), essentially. + /// + /// + /// + /// + /// + /// + /// public class UnhandledOnErrorResumeNextInspection : ParseTreeInspectionBase { private readonly Dictionary, List> _unhandledContextsMap = diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection/UnreachableCaseInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection/UnreachableCaseInspection.cs index 313b0fa14c..a1f68a4f54 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection/UnreachableCaseInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection/UnreachableCaseInspection.cs @@ -16,6 +16,31 @@ namespace Rubberduck.Inspections.Concrete.UnreachableCaseInspection { + /// + /// Flags 'Case' blocks that are semantically unreachable. + /// + /// + /// Unreachable code is certainly unintended, and is probably either redundant, or a bug. + /// + /// + /// Not all unreachable 'Case' blocks may be flagged, depending on expression complexity. + /// + /// + /// + /// public sealed class UnreachableCaseInspection : ParseTreeInspectionBase { private readonly IUnreachableCaseInspectorFactory _unreachableCaseInspectorFactory; diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UntypedFunctionUsageInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UntypedFunctionUsageInspection.cs index 2e524f4863..e09c0d9d94 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UntypedFunctionUsageInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UntypedFunctionUsageInspection.cs @@ -10,6 +10,27 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Flags uses of a number of specific string-centric but Variant-returning functions in various standard library modules. + /// + /// + /// Several functions in the standard library take a Variant parameter and return a Variant result, but an equivalent + /// string-returning function taking a string parameter exists and should probably be preferred. + /// + /// + /// + /// + /// + /// + /// public sealed class UntypedFunctionUsageInspection : InspectionBase { public UntypedFunctionUsageInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UseMeaningfulNameInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UseMeaningfulNameInspection.cs index 796142a668..4ac1b94e95 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UseMeaningfulNameInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UseMeaningfulNameInspection.cs @@ -15,6 +15,27 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about identifiers that have names that are likely to be too short, disemvoweled, or appended with a numeric suffix. + /// + /// + /// Meaningful, pronounceable, unabbreviated names read better and leave less room for interpretation. + /// Moreover, names suffixed with a number can indicate the need to look into an array, collection, or dictionary data structure. + /// + /// + /// + /// + /// + /// + /// public sealed class UseMeaningfulNameInspection : InspectionBase { private readonly IConfigurationService _settings; diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotAssignedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotAssignedInspection.cs index 1c2ce66d67..ffe991126e 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotAssignedInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotAssignedInspection.cs @@ -12,6 +12,31 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about variables that are never assigned. + /// + /// + /// A variable that is never assigned is probably a sign of a bug. + /// This inspection may yield false positives if the variable is assigned through a ByRef parameter assignment, or + /// if UserForm controls fail to resolve, references to these controls in code-behind can be flagged as unassigned and undeclared variables. + /// + /// + /// + /// + /// + /// + /// public sealed class VariableNotAssignedInspection : InspectionBase { public VariableNotAssignedInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotUsedInspection.cs index df2069603b..34305a5fb0 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotUsedInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotUsedInspection.cs @@ -13,6 +13,30 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about variables that are never referenced. + /// + /// + /// A variable can be declared and even assigned, but if its value is never referenced, it's effectively an unused variable. + /// + /// + /// + /// + /// + /// + /// public sealed class VariableNotUsedInspection : InspectionBase { public VariableNotUsedInspection(RubberduckParserState state) : base(state) { } diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableTypeNotDeclaredInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableTypeNotDeclaredInspection.cs index 4f689de1d5..226cc04414 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableTypeNotDeclaredInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableTypeNotDeclaredInspection.cs @@ -10,6 +10,30 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about variables declared without an explicit data type. + /// + /// + /// A variable declared without an explicit data type is implicitly a Variant/Empty until it is assigned. + /// + /// + /// + /// + /// + /// + /// public sealed class VariableTypeNotDeclaredInspection : InspectionBase { public VariableTypeNotDeclaredInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/WriteOnlyPropertyInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/WriteOnlyPropertyInspection.cs index 4a36003a7e..be0d66d53a 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/WriteOnlyPropertyInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/WriteOnlyPropertyInspection.cs @@ -10,6 +10,35 @@ namespace Rubberduck.Inspections.Concrete { + /// + /// Warns about properties that don't expose a 'Property Get' accessor. + /// + /// + /// Write-only properties are suspicious: if the client code is able to set a property, it should be allowed to read that property as well. + /// Class design guidelines and best practices generally recommend against write-only properties. + /// + /// + /// + /// + /// + /// + /// public sealed class WriteOnlyPropertyInspection : InspectionBase { public WriteOnlyPropertyInspection(RubberduckParserState state) diff --git a/Rubberduck.CodeAnalysis/QuickFixes/QuickFixProvider.cs b/Rubberduck.CodeAnalysis/QuickFixes/QuickFixProvider.cs index 3788216a83..9db846ea2a 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/QuickFixProvider.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/QuickFixProvider.cs @@ -37,14 +37,19 @@ public QuickFixProvider(IRewritingManager rewritingManager, IQuickFixFailureNoti } } - public IEnumerable QuickFixes(IInspectionResult result) + public IEnumerable QuickFixes(Type inspectionType) { - if (!_quickFixes.ContainsKey(result.Inspection.GetType())) + if (!_quickFixes.ContainsKey(inspectionType)) { return Enumerable.Empty(); } - return _quickFixes[result.Inspection.GetType()].Where(fix => + return _quickFixes[inspectionType]; + } + + public IEnumerable QuickFixes(IInspectionResult result) + { + return QuickFixes(result.Inspection.GetType()).Where(fix => { string value; try diff --git a/Rubberduck.CodeAnalysis/QuickFixes/ReplaceWhileWendWithDoWhileLoopQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/ReplaceWhileWendWithDoWhileLoopQuickFix.cs new file mode 100644 index 0000000000..e01e366d1f --- /dev/null +++ b/Rubberduck.CodeAnalysis/QuickFixes/ReplaceWhileWendWithDoWhileLoopQuickFix.cs @@ -0,0 +1,30 @@ +using Rubberduck.CodeAnalysis.Inspections.Concrete; +using Rubberduck.Inspections.Abstract; +using Rubberduck.Parsing.Grammar; +using Rubberduck.Parsing.Inspections.Abstract; +using Rubberduck.Parsing.Rewriter; + +namespace Rubberduck.CodeAnalysis.QuickFixes +{ + public sealed class ReplaceWhileWendWithDoWhileLoopQuickFix : QuickFixBase + { + public ReplaceWhileWendWithDoWhileLoopQuickFix() + : base(typeof(ObsoleteWhileWendStatementInspection)) + { } + + public override void Fix(IInspectionResult result, IRewriteSession rewriteSession) + { + var rewriter = rewriteSession.CheckOutModuleRewriter(result.QualifiedSelection.QualifiedName); + var context = (VBAParser.WhileWendStmtContext)result.Context; + + rewriter.Replace(context.WHILE(), "Do While"); + rewriter.Replace(context.WEND(), "Loop"); + } + + public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.ReplaceWhileWendWithDoWhileLoopQuickFix; + + public override bool CanFixInProcedure => true; + public override bool CanFixInModule => true; + public override bool CanFixInProject => true; + } +} diff --git a/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.csproj b/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.csproj index c7416eb62d..af34dd7e29 100644 --- a/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.csproj +++ b/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.csproj @@ -8,6 +8,9 @@ Rubberduck.CodeAnalysis {DEF2FB9D-6E62-49D6-8E26-9983AC025768} + + Rubberduck.CodeAnalysis.xml + diff --git a/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.xml b/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.xml new file mode 100644 index 0000000000..c7153eb96e --- /dev/null +++ b/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.xml @@ -0,0 +1,2334 @@ + + + + Rubberduck.CodeAnalysis + + + + + The name of the metric. Used for localization purposes as well as a uniquely identifying name to disambiguate between metrics. + + + + + The aggregation level that this metric applies to. + + + + + A CodeMetricsResult. Each result is attached to a Declaration. + Usually this declaration would be a Procedure (Function/Sub/Property). + Some metrics are only useful on Module level, some even on Project level. + + Some metrics may be aggregated to obtain a metric for a "higher hierarchy level" + + + + + The declaration that this result refers to. + + + + + The Metric kind that this result belongs to. Only results belonging to the **same** metric can be aggregated. + + + + + A string representation of the value. + + + + + Flags 'While...Wend' loops as obsolete. + + + 'While...Wend' loops were made obsolete when 'Do While...Loop' statements were introduced. + 'While...Wend' loops cannot be exited early without a GoTo jump; 'Do...Loop' statements can be conditionally exited with 'Exit Do'. + + + + + + + + + + + Default constructor required for XML serialization. + + + + + Gets a localized string representing a short name/description for the inspection. + + + + + Gets the type of inspection; used for regrouping inspections. + + + + + The inspection type name, obtained by reflection. + + + + + Inspection severity level. Can control whether an inspection is enabled. + + + + + Meta-information about why an inspection exists. + + + + + Gets a localized string representing the type of inspection. + + + + + + Gets a string representing the text that must be present in an + @Ignore annotation to disable the inspection at a given site. + + + + + Gets all declarations in the parser state without an @Ignore annotation for this inspection. + + + + + Gets all user declarations in the parser state without an @Ignore annotation for this inspection. + + + + + A method that inspects the parser state and returns all issues it can find. + + + + + + + Gets the information needed to select the target instruction in the VBE. + + + + + WARNING: This property can have side effects. It can change the ActiveVBProject if the result has a null Declaration, + which causes a flicker in the VBE. This should only be called if it is *absolutely* necessary. + + + + + Locates public User-Defined Function procedures accidentally named after a cell reference. + + + + Another good reason to avoid numeric suffixes: if the function is meant to be used as a UDF in a cell formula, + the worksheet cell by the same name takes precedence and gets the reference, and the function is never invoked. + + + + + + + + + + + Identifies uses of 'IsMissing' involving a non-parameter argument. + + + 'IsMissing' only returns True when an optional Variant parameter was not supplied as an argument. + This inspection flags uses that attempt to use 'IsMissing' for other purposes, resulting in conditions that are always False. + + + + + + + + + + + Warns about 'Declare' statements that are using the obsolete/unsupported 'CDecl' calling convention on Windows. + + + The CDecl calling convention is only implemented in VBA for Mac; if Rubberduck can see it (Rubberduck only runs on Windows), + then the declaration is using an unsupported (no-op) calling convention on Windows. + + + + + + + + + + + Flags usages of members marked as obsolete with an @Obsolete("justification") Rubberduck annotation. + + + Marking members as obsolete can help refactoring a legacy code base. This inspection is a tool that makes it easy to locate obsolete member calls. + + + + + + + + + + + A ThunderCode inspection that locates instances of various keywords and reserved identifiers used as Type or Enum member names. + + + This inpection is flagging code we dubbed "ThunderCode", + code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + While perfectly legal as Type or Enum member names, these identifiers should be avoided: + they need to be square-bracketed everywhere they are used. + + + + + A ThunderCode inspection that locates certain specific instances of line continuations in places we'd never think to put them. + + + This inpection is flagging code we dubbed "ThunderCode", + code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + While perfectly legal, these line continuations serve no purpose and should be removed. + + + Note that the inspection only checks a subset of possible "evil" line continatuions + for both simplicity and performance reasons. Exhaustive inspection would likely take too much effort. + + + + + A ThunderCode inspection that locates negative line numbers. + + + This inpection is flagging code we dubbed "ThunderCode", + code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + The VBE does allow rather strange and unbelievable things to happen. + + + + + A ThunderCode inspection that locates non-breaking spaces hidden in identifier names. + + + This inpection is flagging code we dubbed "ThunderCode", + code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + This inspection may accidentally reveal non-breaking spaces in code copied and pasted from a website. + + + + + A ThunderCode inspection that locates instances of 'On Error GoTo -1' statements. + + + This inpection is flagging code we dubbed "ThunderCode", + code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + 'On Error GoTo -1' is poorly documented and uselessly complicates error handling. + + + + + Warns about parameters passed by value being assigned a new value in the body of a procedure. + + + Debugging is easier if the procedure's initial state is preserved and accessible anywhere within its scope. + Mutating the inputs destroys the initial state, and makes the intent ambiguous: if the calling code is meant + to be able to access the modified values, then the parameter should be passed ByRef; the ByVal modifier might be a bug. + + + + + + + + + + + Warns about a variable that is assigned, and then re-assigned before the first assignment is read. + + + The first assignment is likely redundant, since it is being overwritten by the second. + + + + + + + + + + + Indicates that the value of a hidden VB attribute is out of sync with the corresponding Rubberduck annotation comment. + + + Keeping Rubberduck annotation comments in sync with the hidden VB attribute values, surfaces these hidden attributes in the VBE code panes; + Rubberduck can rewrite the attributes to match the corresponding annotation comment. + + + + + + + + + + + Identifies redundant Boolean expressions in conditionals. + + + A Boolean expression never needs to be compared to a Boolean literal in a conditional expression. + + + + + + + + + + + Locates 'Const' declarations that are never referenced. + + + Declarations that are never used should be removed. + + + + + + + + + + + This inspection means to indicate when the project has not been renamed. + + + VBA projects should be meaningfully named, to avoid namespace clashes when referencing other VBA projects. + + + + + Warns about Def[Type] statements. + + + These declarative statements make the first letter of identifiers determine the data type. + + + + + + + + Warns about duplicated annotations. + + + Rubberduck annotations should not be specified more than once for a given module, member, variable, or expression. + + + + + + + + + + + Identifies empty 'Case' blocks that can be safely removed. + + + Case blocks in VBA do not "fall through"; an empty 'Case' block might be hiding a bug. + + + 0 + Debug.Print foo ' does not run if foo is 0. + End Select + End Sub + ]]> + + + 0 + '...code... + End Select + End Sub + ]]> + + + + + Identifies empty 'Do...Loop While' blocks that can be safely removed. + + + Dead code should be removed. A loop without a body is usually redundant. + + + + + + + + + + + Identifies empty 'Else' blocks that can be safely removed. + + + Empty code blocks are redundant, dead code that should be removed. They can also be misleading about their intent: + an empty block may be signalling an unfinished thought or an oversight. + + + + + + + + + + + Identifies empty 'For Each...Next' blocks that can be safely removed. + + + Dead code should be removed. A loop without a body is usually redundant. + + + + + + + + + + + Identifies empty 'For...Next' blocks that can be safely removed. + + + Dead code should be removed. A loop without a body is usually redundant. + + + + + + + + + + + Identifies empty 'If' blocks. + + + Conditional expression is inverted; there would not be a need for an 'Else' block otherwise. + + + + + + + + + + + Flags empty code modules. + + + An empty module does not need to exist and can be safely removed. + + + + + Flags uses of an empty string literal (""). + + + Standard library constant 'vbNullString' is more explicit about its intent, and should be preferred to a string literal. + While the memory gain is meaningless, an empty string literal still takes up 2 bytes of memory, + but 'vbNullString' is a null string pointer, and doesn't. + + + + + + + + + + + Identifies empty 'While...Wend' blocks that can be safely removed. + + + Dead code should be removed. A loop without a body is usually redundant. + + + + + + + + + + + Flags publicly exposed instance fields. + + + Instance fields are the implementation details of a object's internal state; exposing them directly breaks encapsulation. + Often, an object only needs to expose a 'Get' procedure to expose an internal instance field. + + + + + + + + + + + Warns about late-bound WorksheetFunction calls made against the extended interface of the Application object. + + + + An early-bound, equivalent function likely exists in the object returned by the Application.WorksheetFunction property; + late-bound member calls will fail at run-time with error 438 if there is a typo (a typo fails to compile for an early-bound member call). + Late-bound worksheet functions will return a Variant/Error given invalid inputs; + the equivalent early-bound member calls raise a more VB-idiomatic runtime error given the same invalid inputs. + A Variant/Error value cannot be coerced into any other data type, be it for assignment or comparison. + Trying to compare or assign a Variant/Error to another data type will throw error 13 "type mismatch" at run-time. + Consider using the early-bound equivalent function instead. + + + 15 Then + ' won't run, error 13 "type mismatch" will be thrown when Variant/Error is compared to an Integer. + End If + End Sub + ]]> + + + 15 Then ' throws error 1004 + ' won't run, error 1004 is thrown when "ABC" is processed by WorksheetFunction.Sum, before it returns. + End If + End Sub + ]]> + + + + Locates instances of member calls made against the result of a Range.Find/FindNext/FindPrevious method, without prior validation. + + + Range.Find methods return a Range object reference that refers to the cell containing the search string; + this object reference will be Nothing if the search didn't turn up any results, and a member call against Nothing will raise run-time error 91. + + + + + + + + + + + Locates unqualified Worksheet.Range/Cells/Columns/Rows member calls that implicitly refer to ActiveSheet. + + + + Implicit references to the active worksheet rarely mean to be working with *whatever worksheet is currently active*. + By explicitly qualifying these member calls with a specific Worksheet object, the assumptions are removed, the code + is more robust, and will be less likely to throw run-time error 1004 or produce unexpected results + when the active sheet isn't the expected one. + + + + + + + + + + + Locates unqualified Workbook.Worksheets/Sheets/Names member calls that implicitly refer to ActiveWorkbook. + + + + Implicit references to the active workbook rarely mean to be working with *whatever workbook is currently active*. + By explicitly qualifying these member calls with a specific Workbook object, the assumptions are removed, the code + is more robust, and will be less likely to throw run-time error 1004 or produce unexpected results + when the active workbook isn't the expected one. + + + + + + + + + + + Locates ThisWorkbook.Worksheets and ThisWorkbook.Sheets calls that appear to be dereferencing a worksheet that is already accessible at compile-time with a global-scope identifier. + + + Sheet names can be changed by the user, as can a worksheet's index in ThisWorkbook.Worksheets. + Worksheets that exist in ThisWorkbook at compile-time are more reliably programmatically accessed using their CodeName, + which cannot be altered by the user without accessing the VBE and altering the VBA project. + + + + Inspection only evaluates hard-coded string literals; string-valued expressions evaluating into a sheet name are ignored. + + + + + + + + + + + Warns when a user function's return value is never used, at any of its call sites. + + + A 'Function' procedure normally means its return value to be captured and consumed by the calling code. + It's possible that not all call sites need the return value, but if the value is systematically discarded then this + means the function is side-effecting, and thus should probably be a 'Sub' procedure instead. + + + + + + + + + + + Warns about host-evaluated square-bracketed expressions. + + + Host-evaluated expressions should be implementable using the host application's object model. + If the expression yields an object, member calls against that object are late-bound. + + + + + + + + + + + Flags identifiers that use [Systems] Hungarian Notation prefixes. + + + Systems Hungarian (encoding data types in variable names) stemmed from a misunderstanding of what its inventor meant + when they described that prefixes identified the "kind" of variable in a naming scheme dubbed Apps Hungarian. + Modern naming conventions in all programming languages heavily discourage the use of Systems Hungarian prefixes. + + + + + + + + + + + Flags invalid Rubberduck annotation comments. + + + Rubberduck is correctly parsing an annotation, but that annotation is illegal in that context. + + + + + + + + + + + + Identifies implicit default member calls. + + + Code should do what it says, and say what it does. Implicit default member calls generally do the opposite of that. + + + + + + + + + + + Highlights implicit Public access modifiers in user code. + + + In modern VB (VB.NET), the implicit access modifier is Private, as it is in most other programming languages. + Making the Public modifiers explicit can help surface potentially unexpected language defaults. + + + + + + + + + + + Warns about 'Function' and 'Property Get' procedures that don't have an explicit return type. + + + All functions return something, whether a type is specified or not. The implicit default is 'Variant'. + + + + + + + + + + + Identifies obsolete 16-bit integer variables. + + + Modern processors are optimized for processing 32-bit integers; internally, a 16-bit integer is still stored as a 32-bit value. + Unless code is interacting with APIs that require a 16-bit integer, a Long (32-bit integer) should be used instead. + + + + + + + + + + + Identifies uses of 'IsMissing' involving non-variant, non-optional, or array parameters. + + + 'IsMissing' only returns True when an optional Variant parameter was not supplied as an argument. + This inspection flags uses that attempt to use 'IsMissing' for other purposes, resulting in conditions that are always False. + + + + + + + + + + + Identifies line labels that are never referenced, and therefore superfluous. + + + Line labels are useful for GoTo, GoSub, Resume, and On Error statements; but the intent of a line label + can be confusing if it isn't referenced by any such instruction. + + + + + + + + + + + Warns about member calls against an extensible interface, that cannot be validated at compile-time. + + + Extensible COM types can have members attached at run-time; VBA cannot bind these member calls at compile-time. + If there is an early-bound alternative way to achieve the same result, it should be preferred. + + + + + + + + + + + Warns about a malformed Rubberduck annotation that is missing an argument. + + + Some annotations require arguments; if the argument isn't specified, the annotation is nothing more than an obscure comment. + + + + + + + + + + + Indicates that a Rubberduck annotation is documenting the presence of a VB attribute that is actually missing. + + + Rubberduck annotations mean to document the presence of hidden VB attributes; this inspection flags annotations that + do not have a corresponding VB attribute. + + + + + + + + + + + Indicates that a hidden VB attribute is present for a member, but no Rubberduck annotation is documenting it. + + + Rubberduck annotations mean to document the presence of hidden VB attributes; this inspection flags members that + do not have a Rubberduck annotation corresponding to the hidden VB attribute. + + + + + + + + + + + Indicates that a hidden VB attribute is present for a module, but no Rubberduck annotation is documenting it. + + + Rubberduck annotations mean to document the presence of hidden VB attributes; this inspection flags modules that + do not have a Rubberduck annotation corresponding to the hidden VB attribute. + + + + + + + + + + + Warns about module-level declarations made using the 'Dim' keyword. + + + Private module variables should be declared using the 'Private' keyword. While 'Dim' is also legal, it should preferably be + restricted to declarations of procedure-scoped local variables, for consistency, since public module variables are declared with the 'Public' keyword. + + + + + + + + + + + Indicates that a user module is missing a @Folder Rubberduck annotation. + + + Modules without a custom @Folder annotation will be grouped under the default folder in the Code Explorer toolwindow. + By specifying a custom @Folder annotation, modules can be organized by functionality rather than simply listed. + + + + + + + + + + + Locates module-level fields that can be moved to a smaller scope. + + + Module-level variables that are only used in a single procedure can often be declared in that procedure's scope. + Declaring variables closer to where they are used generally makes the code easier to follow. + + + + + + + + + + + Flags parameters declared across multiple physical lines of code. + + + When splitting a long list of parameters across multiple lines, care should be taken to avoid splitting a parameter declaration in two. + + + + + + + + + + + Flags declaration statements spanning multiple physical lines of code. + + + Declaration statements should generally declare a single variable. + + + + + + + + + + + Warns about 'Function' and 'Property Get' procedures whose return value is not assigned. + + + Both 'Function' and 'Property Get' accessors should always return something. Omitting the return assignment is likely a bug. + + + + + + + + + + + A visitor that visits a member's body and returns true if any LET statement (assignment) is assigning the specified name. + + + + + Warns about assignments that appear to be assigning an object reference without the 'Set' keyword. + + + Omitting the 'Set' keyword will Let-coerce the right-hand side (RHS) of the assignment expression. If the RHS is an object variable, + then the assignment is implicitly assigning to that object's default member, which may raise run-time error 91 at run-time. + + + + + + + + + + + Locates explicit 'Call' statements. + + + The 'Call' keyword is obsolete and redundant, since call statements are legal and generally more consistent without it. + + + + + + + + + + + Locates legacy 'Rem' comments. + + + Modern VB comments use a single quote character (') to denote the beginning of a comment: the legacy 'Rem' syntax is obsolete. + + + + + + + + + + + Locates legacy 'Error' statements. + + + The legacy syntax is obsolete; prefer 'Err.Raise' instead. + + + + + + + + + + + Locates legacy 'Global' declaration statements. + + + The legacy syntax is obsolete; use the 'Public' keyword instead. + + + + + + + + + + + Locates explicit 'Let' assignments. + + + The legacy syntax is obsolete/redundant; prefer implicit Let-coercion instead. + + + + + + + + + + + Flags declarations where a type hint is used in place of an 'As' clause. + + + Type hints were made obsolete when declaration syntax introduced the 'As' keyword. Prefer explicit type names over type hint symbols. + + + + + + + + + + + Flags obsolete 'On Local Error' statements. + + + All errors are "local" - the keyword is redundant/confusing and should be removed. + + + + + + + + + + + Flags modules that specify Option Base 1. + + + Implicit array lower bound is 0 by default, and Option Base 1 makes it 1. While compelling in a 1-based environment like the Excel object model, + having an implicit lower bound of 1 for implicitly-sized user arrays does not change the fact that arrays are always better off with explicit boundaries. + Because 0 is always the lower array bound in many other programming languages, this option may trip a reader/maintainer with a different background. + + + + + + + + + + + Flags modules that omit Option Explicit. + + + This option makes variable declarations mandatory. Without it, a typo gets compiled as a new on-the-spot Variant/Empty variable with a new name. + Omitting this option amounts to refusing the little help the VBE can provide with compile-time validation. + + + + + + + + + + + Flags parameters that are passed by reference (ByRef), but could be passed by value (ByVal). + + + Explicitly specifying a ByVal modifier on a parameter makes the intent explicit: this parameter is not meant to be assigned. In contrast, + a parameter that is passed by reference (implicitly, or explicitly ByRef) makes it ambiguous from the calling code's standpoint, whether the + procedure might re-assign these ByRef values and introduce a bug. + + + + + + + + + + + Identifies parameter declarations that are not used. + + + Declarations that are not used anywhere should probably be removed. + + + Not all unused parameters can/should be removed: ignore any inspection results for + event handler procedures and interface members that Rubberduck isn't recognizing as such. + + + + + + + + + + + Warns about 'Sub' procedures that could be refactored into a 'Function'. + + + Idiomatic VB code uses 'Function' procedures to return a single value. If the procedure isn't side-effecting, consider writing is as a + 'Function' rather than a 'Sub' the returns a result through a 'ByRef' parameter. + + + + + + + + + + + Locates procedures that are never invoked from user code. + + + Unused procedures are dead code that should probably be removed. Note, a procedure may be effectively "not used" in code, but attached to some + Shape object in the host document: in such cases the inspection result should be ignored. An event handler procedure that isn't being + resolved as such, may also wrongly trigger this inspection. + + + Not all unused procedures can/should be removed: ignore any inspection results for + event handler procedures and interface members that Rubberduck isn't recognizing as such. + + + + + + + + + + + We cannot determine whether exposed members of standard modules are called or not, + so we assume they are instead of flagging them as "never called". + + + + + Identifies redundant ByRef modifiers. + + + Out of convention or preference, explicit ByRef modifiers could be considered redundant since they are the implicit default. + This inspection can ensure the consistency of the convention. + + + + + + + + + + + Identifies redundant module options that are set to their implicit default. + + + Module options that are redundant can be safely removed. Disable this inspection if your convention is to explicitly specify them; a future + inspection may be used to enforce consistently explicit module options. + + + + + + + + + + + Identifies auto-assigned object declarations. + + + Auto-assigned objects are automatically re-created as soon as they are referenced. It is therefore impossible to set one such reference + to 'Nothing' and then verifying whether the object 'Is Nothing': it will never be. This behavior is potentially confusing and bug-prone. + + + + + + + + + + + Identifies identifiers that hide/"shadow" other identifiers otherwise accessible in that scope. + + + Global namespace contains a number of perfectly legal identifier names that user code can use. But using these names in user code + effectively "hides" the global ones. In general, avoid shadowing global-scope identifiers if possible. + + + + + + + + + + + Locates 'For' loops where the 'Step' token is omitted. + + + Out of convention or preference, explicit 'Step' specifiers could be considered mandatory; + this inspection can ensure the consistency of the convention. + + + + + + + + + + + Locates 'For' loops where the 'Step' token is specified with the default increment value (1). + + + Out of convention or preference, explicit 'Step 1' specifiers could be considered redundant; + this inspection can ensure the consistency of the convention. + + + + + + + + + + + Locates 'Stop' instructions in user code. + + + While a great debugging tool, 'Stop' instructions should not be reachable in production code; this inspection makes it easy to locate them all. + + + + + + + + + + + Warns when a variable is referenced prior to being assigned. + + + An uninitialized variable is being read, but since it's never assigned, the only value ever read would be the data type's default initial value. + Reading a variable that was never written to in any code path (especially if Option Explicit isn't specified), is likely to be a bug. + + + This inspection may produce false positives when the variable is an array, or if it's passed by reference (ByRef) to a procedure that assigns it. + + + + + + + + + + + Warns about implicit local variables that are used but never declared. + + + If this code compiles, then Option Explicit is omitted and compile-time validation is easily forfeited, even accidentally (e.g. typos). + + + + + + + + + + + Warns about public class members with an underscore in their names. + + + The public interface of any class module can be implemented by any other class module; if the public interface + contains names with underscores, other classes cannot implement it - the code will not compile. Avoid underscores; prefer PascalCase names. + + + + + + + + + + + Finds instances of 'On Error Resume Next' that don't have a corresponding 'On Error GoTo 0' to restore error handling. + + + 'On Error Resume Next' should be constrained to a limited number of instructions, otherwise it supresses error handling + for the rest of the procedure; 'On Error GoTo 0' reinstates error handling. + This inspection helps treating 'Resume Next' and 'GoTo 0' as a code block (similar to 'With...End With'), essentially. + + + + + + + + + + + Flags 'Case' blocks that are semantically unreachable. + + + Unreachable code is certainly unintended, and is probably either redundant, or a bug. + + + Not all unreachable 'Case' blocks may be flagged, depending on expression complexity. + + + + + + + + Flags uses of a number of specific string-centric but Variant-returning functions in various standard library modules. + + + Several functions in the standard library take a Variant parameter and return a Variant result, but an equivalent + string-returning function taking a string parameter exists and should probably be preferred. + + + + + + + + + + + Warns about identifiers that have names that are likely to be too short, disemvoweled, or appended with a numeric suffix. + + + Meaningful, pronounceable, unabbreviated names read better and leave less room for interpretation. + Moreover, names suffixed with a number can indicate the need to look into an array, collection, or dictionary data structure. + + + + + + + + + + + Warns about variables that are never assigned. + + + A variable that is never assigned is probably a sign of a bug. + This inspection may yield false positives if the variable is assigned through a ByRef parameter assignment, or + if UserForm controls fail to resolve, references to these controls in code-behind can be flagged as unassigned and undeclared variables. + + + + + + + + + + + Warns about variables that are never referenced. + + + A variable can be declared and even assigned, but if its value is never referenced, it's effectively an unused variable. + + + + + + + + + + + Warns about variables declared without an explicit data type. + + + A variable declared without an explicit data type is implicitly a Variant/Empty until it is assigned. + + + + + + + + + + + Warns about properties that don't expose a 'Property Get' accessor. + + + Write-only properties are suspicious: if the client code is able to set a property, it should be allowed to read that property as well. + Class design guidelines and best practices generally recommend against write-only properties. + + + + + + + + + + + Determines whether the 'Set' keyword is required (whether it's present or not) for the specified identifier reference. + + The identifier reference to analyze + The parser state + + + + A code inspection quickfix that removes an unused identifier declaration. + + + + diff --git a/Rubberduck.Core/UI/AddRemoveReferences/AddRemoveReferencesDialog.resx b/Rubberduck.Core/UI/AddRemoveReferences/AddRemoveReferencesDialog.resx index 0a0a5023e2..634185d01a 100644 --- a/Rubberduck.Core/UI/AddRemoveReferences/AddRemoveReferencesDialog.resx +++ b/Rubberduck.Core/UI/AddRemoveReferences/AddRemoveReferencesDialog.resx @@ -120,26 +120,258 @@ - AAABAAEAEBAAAAEAIABoBAAAFgAAACgAAAAQAAAAIAAAAAEAIAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA - AAAAAAAAAAAAAAAAAAEAAAAAAAAABwAAAAgAAAAGAAAABwAAAAgAAAADAAAAAAAAAAAAAAAAAAAAAAAA - AAAAAAAAAAAAAAAAAAABAwNEAAAA/zpkZP8uXmP/LGBl/y9hY/80ZGP/OWlo/0t2dP8AAAD/AAAAxwEC - AogAAAAAAAAAAAAAAAAAAQGTCicr/zTk+f9U3v//RtX//0rV//9P3f//Ve3//y/p//855/v/Qv3//1T/ - //8MLS/+AAAA0QAAAAAAAQGRBBMW/zXn/f846v//SNz9/0jL/v8xvv//OMv//0DU//8/3v3/L+j//zTo - //8r4/z/Svr//0mAf/4BAgKIISko/ynQ5v8x6P//Men//y7Z7v9ApLn/LrH4/y+y9f84vfT/K57K/y/l - +v8x5///L+j//0v2//+M////AAAAihIsLf8w7f//MOr//zXq//8x6f//JK6+/yeIp/8gZoL/LYyq/ynF - 2f8w5/7/MOj//zTq//9K9P//g////wAAAJUAAADSROX//1LK//9E5f//OO7//zLr//8w4ff/L+X7/y/j - +v8x6P//N+z//zHo//8s5v//gv3//7j///4AAACcAAAAlD+Cof87c4z/RGNj/zRdY/8xoK7+LfX//xrm - //8c2v//IeD//zDx//9G+P//Vvr//9z///8kKir/AAAAAAAAAFYAAABtAAAAGgAAAAgAAAALAAAA2yTb - +v8Y0f//HNr//xzf//8z+///Yv///2y8vP4qMjL/BAUFMwAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA3Cac - r/8t0/7/Icn//x7Y//8o+P7/Sv///wAAAP8AAACgAAAAAAAAAAEAAAAAAAAAAAAAAAAAAAAAAAAAEwwh - I/873P//JMj//xS8//8Wyv//Gpi2/wIADv8LCgC5AAAABQAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA - ACUqYWT/Mtb//xy6//8Gt/7/Htr//xlhbP8fRvX/O1Hs/jlCctsAAAADAAAAAAAAAAAAAAAAAAAAAAAA - AAAAAAAaSGpo/0vZ//4Zs///n+z//wAAAP9FVFz/E0Gh/z1G//9AS2j/AAAAAwAAAAAAAAAAAAAAAAAA - AAAAAAAAAAAABAAAAKiS8/7MOr3//pLc/v/v////Pmxs/zBBPcIAAAD/ISEv/wAAAAQAAAAAAAAAAAAA - AAAAAAAAAAAAAAAAAAAAAABNAAAAtqXk8shM0v//Ppac/wAAAP8AAAA2AAAAAAAAAAcAAAABAAAAAAAA - AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA0AAACfAAAAlAAAAIAAAAA3AAAAAQAAAAAAAAAAAAAAAAAA - AAAAAAAA//8AAOADAACAAQAAAAAAAAAAAAAAAAAAAAAAAAABAAD4AwAA8AcAAPAPAADwBwAA8AcAAPAH - AAD4PwAA/H8AAA== + AAABAAMAEBAAAAEAIABoBAAANgAAACAgAAABACAAqBAAAJ4EAAAwMAAAAQAgAKglAABGFQAAKAAAABAA + AAAgAAAAAQAgAAAAAAAABAAAww4AAMMOAAAAAAAAAAAAAAAAAAAAAAAARVhaAENbXQRJUVEoSVNUWElV + V3lJV1mGSVZYfUlVVltIU1QmQGJmA0NdYAAAAAAAAAAAAAAAAAA9cXgATklIAEdYWiZHXmOWQHqF3zmV + p/g1pr3+M63F/zWov/85lqj5QHiD3UdeYpBHWFolWi0mADd+iAAAAAAATkpJAEhVVi1Ea3LLM6zE/yrU + 9v8o3f//J93//yfd//8n3f//KN3//yrT9f80qsH/Q2520kZbXkBZLygAMoyaAENeYhJFZWu0MbTO/yfd + //8o2///KNv//yjb//8o2///KNv//yjb//8o3P//J93//y++2v9DbnbPRltdHkRhZgBIVlhfOpGi9yjb + /v8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8n3f//OJuu/UhWWFxLUVIARl9kqTG3 + 0f8n3f//KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///J97//zSpv/9JVlluTU5OAEVm + bMYuxOL/KNz//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjc//86lKX6SVRVUEtT + VABFZWvBLsLg/yjc//8o3P//J93//yja/f8p2Pv/KNv+/yjb//8o2///KNv//yjd//8uwNz/RGpyxUZY + WhVEY2cAR19jqDC50/8n3v//Lcfm/zaiuP49iJfvP3+L6TuQof4q0/X/KNz//yjc//8syur/QHqG6ERl + a0xNTU0AMZiqAEhYWnU4mKv9N5+0/ENsdMpIWFtwSVFSNUlVV5M7jZ3/Kdj7/yjb//8o3P//LcTi+z6E + j3U+f2cDPIqJAAAAAABGXWA6SF1g1UdcX4BFWVsWS1FTAEdWWDBAe4fkKtHx/yjc//8o2///KNz//zSo + wPs/YXvPRVZkmUZiYCZRSUIAP210CEZcYCNDYGQEQmNnAE1OTgBJVlhmNqK3/yfe//8o2///KdX3/yrS + 9P84ma3/MFmh/yVcw/9BV3HDRmNhIgAAAAAAAAAAAAAAAAAAAABOS0sASFlccDWnvf8n3v//KN3//zSr + wv85lab/K8/t/z9pgP41VpTyQVRv6kdeX1UAAAAAAAAAAAAAAAAAAAAASFhbAEhXWT0+gI3uKtDx/yfe + //8q0/P/LMrq/zWnvv9GYWWyTFdPO0deXC9Aa3IOAAAAAAAAAAAAAAAAAAAAAD1zewA6dn8ER1pdbj98 + iOc1p73/MrDJ/zuOn/ZFY2inRGBkHkdZXAAgtbwAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAQGhtADxx + eQNHVlg6SVdZgUlXWZBIVlhZQmJmDkhUVQAM4fYAAAAAAAAAAADgDwAAwAcAAIADAAAAAQAAAAEAAAAB + AAAAAQAAAAEAAAADAAAAAwAACAEAABgAAAD4AAAA+AAAAPgHAAD8DwAAKAAAACAAAABAAAAAAQAgAAAA + AAAAEAAAww4AAMMOAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAhs8kADt3pAi+SoAk9c3sQRGJmFDh+iR1DZGkRMouYDBfJ1gP/AAAAAP//AAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAHb3KAAXz + /wE7dn4SQWhuQUZdYHJIWFqdSlNUuUtRUclNTUzNSlJT2ExOTstKU1TASFhbo0RhZXZBaXA9N3+KDwD/ + /wAS1d8AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAJaq+AAD/ + /wE/bnUiRl1hfUpTVMxLUVH0SVha/0ZmbP9CdX//PoGO/zyIl/88ipn/PYSS/0F4g/9FZ27/SVha/0tR + UfNJVVbFRGFmbzt3fxoA//8AFszZAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAADWE + kAAwkJ8HQmZsY0pTVNlKVVf+QXaA/zagtf8uv9z/KtDw/ynX+v8o2/7/J9z//yfc//8o2///KNj8/yrR + 8v8uvtv/N5yw/0NweP9LU1T8SVVX0EJnbVwxjZkHOXyGAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AABBaW8APXJ7BkhZXHpLUVL2QnF6/zG0zv8p1vn/J93//yjd//8o3P//KNv//yjb//8o2///KNv//yjb + //8o2///KNz//yjd//8n3f//KdP1/zOsxP9DbHT/S1FR9UZdYJA2go4UQGtyAAby/wAAAAAAAAAAAAAA + AAAAAAAAMY2aAB660gRFX2N4TFBQ9j2Ekf8qz+//J93//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o3P//J93//yrO7v87ipr/S1NU/kVeYqs0hpIWOHyHAAAA + AAAAAAAAAAAAACmfsgBPSUgAQWpwUUtRUvA+f4v/KdPz/yjc//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNz//yjY+v85l6n/S1NV/0Vg + ZJEjrsAGMJGdAAAAAAAAAAAAOniCADh+iRhJVlfIRWhu/yvJ6P8o3P//KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNz//yjY + +v88iJf/S1JT8T9tdERFYGUAAP//AAAAAABWOTUAQmZra0tTVP00qL7/J93//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KN3//y3F4v9IXWH/R1tek/8AAAAoorQAAAAAADaBjQxKVFa5RGx0/yrS8v8o3P//KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNj6/0F2gP9JVVfCLpSkCzCRoAAAAAAAPm93NUtRUek5lKb/J93//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///PoOQ/0tQUc0+cHcPPnB4AAAAAABCZWtiSlNV+jGy + y/8n3f//KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yja/v8/f4v/S1FSyjp5gg46eYMAAAAAAEZe + YX5JWVv/LsHe/yjd//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o3P//KdP0/0Rsc/9JVVavJqi8BTGO + nAAAAAAASVVXf0lbXv8txeP/KNz//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yfd//8xtM7/SlVX/0Vf + Y3NYNC8AD9v1AAAAAABFYGR/SVlc/y7B3v8o3f//KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o3P//KdX2/0B5 + g/9KUlPdPnB4Jj9scwAAAAAAAAAAAEZdYGlKVVf8L7vW/yjd//8o2///KNv//yjb//8o2///KNv//yjc + //8o3f//J93//yfd//8n3f//J93//yjc//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + /v83nK//S1FS/EVgZHX/AAAALJmqAAAAAAAAAAAAQ2NoV0tTVPgysMn/J93//yjb//8o2///KNv//yjd + //8o2/3/K83t/zC30v81pLr/OJqt/zebr/80qL//LcLg/yja/v8o2///KNv//yjb//8o2///KNv//yjb + //8o3P//M6zD/0lYWv9EZmvAMputFzaPnwAAAAAAAAAAAAAAAABAanE5S1BR7Decr/8n3f//KNv//yjd + //8p1vf/MbXP/z2GlP9GY2n/SlVX/ktQUfJMT1DoS1BR7U1NTf5FZ23/K8zs/yjc//8o2///KNv//yjb + //8o2///KNz//zGxy/9IW17/R11g0DSYqDZgAAcAE/v/ACjb/wAAAAAAAAAAADp5ghdKUlPPPn+M/yjb + /v8o2vz/MLfR/0B4g/9KVVf+SlJT40hZW6NEYGVjQ2VqOT9scypFYGSeTE9Q/zqOnv8o1/r/KNv//yjb + //8o2///KNv//yjb//8o2///Oo+f/0dhZto7g5A6Vzs+ABXh8gAAAAAAAAAAAAAAAAAAAAAAAP//AkhX + WaBGZWv/LcDd/zqPoP9KV1r/SlNU3UNkaYA7dn8oJ6W4BC+SoQBYMy4AQGtxVEtRUvA+f4v/KdP0/yjc + //8o2///KNv//yjb//8o2///KNv//yjb//8q0/X7K8roeAD//wFPw/kAAP//AAAAAAAAAAAAAAAAAAAA + AABOS0oARGFmZktTVP9HYWb/S1FS9UZdYZ49cXknAP//ASKwwwAAAAAAPnB4ADt3gB5JVVfQRWpx/yvK + 6f8o3P//KNv//yjb//8o2///KNv//yjb//8o2///KNr9/y692fg/e4W4SFpaokZfYn8/bnUtDt37ASao + ugAAAAAAAAAAAD9udQA9cXkvSlRW6kpSVN1DZWpdLZioCDWFkQAAAAAAAAAAACaotgBVOzcARGBldEpV + Vv8yrsb/J93//yjb//8o2///KNv//yjb//8o2///KNv//yjd//8xssv/SVpd/0dPX/9CUW7/SU9a/0pV + VeFBaW9hIbPJBC+TogAAAAAAL5OiAC6VpQZDZGpIQWlwLQD//wAmqLwAAAAAAAAAAAAAAAAAMYybACKw + xgRJVVeuRGxz/ynT9P8o3P//KNv//yjb//8o2///KNv//yjc//8o3P//J93//zGzzP9LUlL/M1aY/xVj + 8v8fX9T/PlJ5/0tTU/JBaG5tFc7pAyyZqQAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAyjZsAMouYDUpTVMZAfIf/KNr9/yjb//8o2///KNv//yjb//8o2///KdP1/yvL6/8o2v3/KNf6/z2G + lP9ITlr/IV7N/w9l//8WYu3/OlSE/0pUVe5Aa3FFRl1gAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAADSHlAA1hZETSVRW0z+Cj/8o2///KNv//yjb//8o2///KNv//ynW+f8+g5D/R2Fl/zC2 + 0P8n3v//K8zr/0VrcP89Unr/IF7S/yRcxv8tWaz/SU5Y/0ZeYZwA//8BAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAMY6cADGOnQ5JVFbHQXiD/yjZ+/8o2///KNv//yjb//8o2///KdT2/0Jy + e/9MUFH/M6vD/yfd//8n3P7/PYOQ/01LTP9KUFb+TE9R9UtQVPlLUlT9RGJmg9IAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAwkJ8A6AAAAEdaXJFIW1//Lr/b/yfd//8o2///KNv//yjb + //8o2///Lcbk/zG10P8p1vj/J93//y+71v9IXWH/SVZY0UNkaG9HXF8/Q2RpSUBsc083gYwTOniCAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAABBaG4APXJ7O0pUVehBdX//K8vq/yfd + //8o2///KNv//yjb//8o3P//J97//yfd//8vudX/RmZs/0lVVt8+cHg4T0lMAAvn7QAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAACmhsQAA//8BRGFlZktQ + UfBDbnb/MbLL/ynU9/8n3P//J93//yjc//8qz/D/N52x/0hdYf9JVVfdPXF5TP8AAAAhs8IAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAADp4 + ggAwkJ8DQmZsWklUVthKVVf+Q3B4/zuNnf83maz/O4yb/0Vob/9LUlP6R1pduT1zezX/AAAAHrnJAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAACOutwAA//8AOniCI0VgZHZJVFa8S1BQ3E1MS+BLUFHcSVZXsUJma140h5MRRWBrAAP4 + +QAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAO3+wAAP//ADOIlAxAanAhTE9QJD9scyAxjpsJUkJJAAvn + +QAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAD/4B///gAD//gAAP/wAAA/4AAAH8AA + AA/AAAAHgAAAB4AAAAcAAAADAAAAAwAAAAMAAAADAAAABwAAAAcAAAAPAAAADwAAAB8AAAA/ADAAP4Dg + AAeD4AADj8AAAf/AAAH/wAAA/8AAAf/gAAH/4AA//+AAf//wAP///AH///8H/ygAAAAwAAAAYAAAAAEA + IAAAAAAAACQAAMMOAADDDgAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAP//ACanxAAN4f0ALpWkCzSIlSFAanEvPHR9TUVg + ZFFMTk5RQGpwbj9udXFLUlRRQGtxUT1xeTw3gIwlKp6vDxHZ9gIWy+kAAP//AAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAADt//AE5LSwAsmqsHO3Z/Kz9tdGZEYWaaSFlcwkhY + WuJLUVLtS1FS+kxOT/xNTEv8TU1N/k1NTf5NTEz8TFBR/UtRUvNJV1nmRl1gy0Jla55AbHNeNYOPJyWq + vgQyipgAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA3i4wCtAAAAOH6IFD5vd2FGXmKySlRV50xP + UP1NS0v/TUtK/01OTv9KVFb/SVte/0ZiaP9EZ27/RGty/0Rqcf9EZmz/SF9j/0pWWf9MT0//TUtL/01L + S/9MUFD8SVZZ4kRiZqQ7doBOLpSiC0pUZgAA//8AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA//8AN4CMACyaqww+cHdgSFlbx0xQ + UfpNS0v/TE5O/0deYv9Ad4L/OZKk/zOqwf8vu9f/LMbl/yvN7f8p0fL/KdP1/ynT9P8pz/D/LMrp/y6/ + 3P8yrcb/OJSm/0B2gP9IW1//TU1N/01MS/9LU1T1Rl5itTt3gE4jrsIIKp2wAAD//wAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAB+4zwA+b3cAM4mWKENk + aapLUlP5TktL/0pWWP8/eoX/NKe+/yzH5v8o1/r/J93//yfd//8o3f//KNz//yjc//8o3P//KNv//yjc + //8o3P//KNz//yjd//8n3f//J93//yjX+v8sxOL/Np6z/0JweP9MUVH/TUtL/0pVV/VCZmyeNYSQJERj + ZwAsmKkAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAJaa8AEpU + VgBBaXAsR1teyE1OTv9MT1D/P3qF/y+40v8o1/n/J93//yjc//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o3P//J93//ynT9P8yq8P/Qm93/01N + Tv9NTk7/R1te0Dx0fEYA//8BKKGpAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAT09sATUxOAEBrcStJVljITUxM/0lYWv82nbH/KNX2/yjd//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjc + //8n3f//KdDx/zeYqv9JWVz/TUtL/0lWWOc7d4FoE9PuBCaouwAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAA3gIsAM4iVJUZdYMdNTEz/SFte/zGsxP8o2/7/KNz//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNz//yfb/v8vtc//RGdt/05LS/9JVljyOniBbAD//wIhsccAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAC6VowAmprcNQ2Rpp01OTv9KV1n/MavC/yfc//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8n3f//LcLf/0Rtdf9OS0v/SFha6zp4 + gklRRUQAC+f/AAAAAAAAAAAAAAAAAAAAAAAAAAAAJau2AFc2NAA+b3ZnS1JT+kxPT/82m67/KNv+/yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KN3//y3D + 4P9EaG7/TktL/0VfY8svk6IbMoyaAAAAAAAAAAAAAAAAAAAAAAAAAAAANYSRADGMmiNHWl3WTktK/z97 + h/8p1fb/KNz//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yfd//8wssv/SlZY/0xQUf4+b3ZyWTAqACWovAAAAAAAAAAAAAAAAAAWzOgA/wAAAD5v + doBMT0//SVlc/y692P8o3f//KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2fv/PYKO/05LSv9GXWDBKaGzDSyZqgAAAAAAAAAAAAAA + AAAziJUAMoyZF0ZcX9JOS0r/O4iW/yja/f8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8n3f//Ma7F/0xQUP9JVVfqOXyGLDl6 + hAAAAAAAAAAAAAAAAABFXmIAQGpxTEtQUfhKVVf/L7rU/yjd//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o3P//LMXi/0la + Xf9LUlP6OniCTj9udQAAAAAAAAAAAAAAAAD/AAAAQ2NokE1MTP9CcHn/KdT2/yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o3P//K8zs/0ZiZ/9MT0/9Q2VqVEVfYwAAAAAAAAAAAAAAAAAmp7sQRl5ixU5LSv85kKH/J9z//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o3P//Ks7u/0Zkaf9MTk79RV9jVEdbXgAAAAAAAAAAAAAAAAA1hZEkSVdZ3kxO + Tv8yqsH/J93//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o3P//LMno/0hdYf9LUFH8Pm92UkJmbAAAAAAAAAAAAAAA + AAA4fYc8SVVX8EtTVf8vutX/KN3//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o3f//L7jS/0tTVP9LUlPvPnB4Mz9s + cwAAAAAAAAAAAAAAAABDZGk8S1BR8ElYWv8twd7/KN3//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8n3P//OJSl/01L + S/9HWl3SMY2bFjKMmgAAAAAAAAAAAAAAAABDYmc8TFBR8ElYW/8twt//KN3//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjc + //8rzOv/RWZs/01NTf9DZGmPAP//ABy/2AAAAAAAAAAAAAAAAAA9cns8SlNV8EpVV/8vvdr/KN3//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yfc//83maz/TU1N/0pVVu06eIE7P210AAAAAAAAAAAAAAAAAAAAAAA0h5Q5SVdZ7UxR + Uv8wt9L/J93//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KN3//y2+2v9HXWH/TU1N/0Jla50Yx+IFLJmqAAAAAAAAAAAAAAAAAAAA + AABBaG4eS1FR2UxQUP8xsMj/J93//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNz//yjc//8o3f//KN3//yjd//8o3P//KNz//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o3P//Ks7u/0Fzff9OS0r/SFda2Dh9hilAanIAAAAAAAAA + AAAAAAAAAAAAAAAAAAA1hZEZSFlb1U1NTf81pbv/J93//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o3P//KN3//yfd//8o1/r/K83u/yzD4f8vu9f/MLjT/y692f8sxuT/KdHz/yjb/v8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjc//8p1PX/PISR/01MS/9JV1n7OoKNcP8A + AAAh0uYAAAAAAAAAAAAAAAAAAAAAAAAAAAAmqLwMR1tevk1LSv84lKX/J93//yjb//8o2///KNv//yjb + //8o2///KNz//yfd//8p0/T/L7jS/ziVp/9Ad4H/RmNp/0lZW/9KVFb/S1NU/0pVV/9IW1//RGlw/ziW + qP8p1vj/KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNz//yjW+P85jZ3/TU5O/0tS + U/47go6pJNz2HCuCngAo4P8AAAAAAAAAAAAAAAAAAAAAAAAAAAAA//8BRGJnnk1LS/8/fIf/KNn8/yjb + //8o2///KNv//yjc//8n3P7/K8jn/zadsP9Cb3f/SlRV/01LS/9NS0v/TE9P/kxQUPVLUVLsSlVW7EtS + U/JNTU3/TkpJ/0laXv8tx+X/KNz//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNj7/ziR + ov9MT0//TE9Q/j9yeq4lw9kfNIakABf//wAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAABNTU0AQ2Vqak1O + Tv9FZWr/Ks7u/yjc//8o2///J93//yrM6/83lqj/RmFm/01MTP9NTEz/S1JT90daXdFFYGSWP210aUBq + cT9DZGorOH2ILkJmbKdMT1D/TE5O/ziPn/8o2Pv/KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o3P//K8vq/0deY/9NTU3/Q2xztC6svx46hpsAAP//AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAA9cnoAOniCQEpTVPRLU1X/L7nT/yfe//8o1/n/M6nA/0Rob/9NTEz/TU1O/0hYW+pDZWqjPHV+TjCR + nxYK6PgBG7/PACKxugB+AAAAO3Z/YUpUVfFNTEz/PYGO/ynU9P8o3P//KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///Kdj7/zWkuv85kqPULrnSNjyKqAAV//8AAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAA2g44ANoOPFUhXWtFNTEv/N5qt/yvI5/89g5D/S1FS/01MS/9KVVbrQGtxmzOI + lTceutIFJ6W5AAAAAAAAAAAAEdj2AEFpbwA2g485SFpc4k5LSv9Bcnv/Ks3s/yjc//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjd//om4f+OH/j/CCHy/wAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAisccAAP//AkRiZ6FNTEz/RWRq/0VmbP9NS0v/S1FS/ERh + Zrw8dX4+HrjQBCmfsgAA//8AAAAAAAAAAAAAAAAAMouYACqdrg1EYmeyTUxM/0dhZf8twNz/KN3//yjb + //8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///J93//ynS8/YzpLqjQGtxe0Bq + cX0+cHhaNoKOIBy/1wErna4AAAAAAAAAAAAAAAAAAAAAAAAAAAAO3v4ATU1NAD9tdGJMUFH+TUxL/01M + TP9JVljoPnB3eyqdrRM+cH4AAP//AAAAAAAAAAAAAAAAAAAAAAAZxd8AVDw5ADxzfGFLUlP5TFBR/zSk + uv8n3f//KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2v3/MbDJ/0Jw + eP5LU1P9TU9N/01PTf9MUVH8SFha2T5vdnctmKgPMI+eAAAAAAAAAAAAAAAAAAAAAAAAAAAANoKOADSF + ki5HWl3pTE9P/0ZdYMY8dH0+BPb/AiOttgAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAtlqYAJqa6CUVf + Y7lNS0v/P3mD/ynV9v8o3P//KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjc + //8rxuT/R15h/05KSv9JTln/QFJ0/z9Sdf9IT1z/TkxL/0tSUvtCZmumLZemHzaBjwAA//8AAAAAAAAA + AAAAAAAAIrDFABrD3QY+b3ddRGFldTWEkB5PSkkAD9z8AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAA3gIsAN4CMJklWWOVMTk//MqnA/yfd//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjc//8qyur/RmJn/05LSf83VY3/FWPz/xRk9/8dYNz/N1WN/0xNT/9MUE//Q2RquTGN + myA6eIIAAP//AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAABDZGkAQmVrN0tQUfJJV1n/LcDc/yjd//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNv//yjc//8o3P//KNv//yjb//8n2///N5iq/01NTf9JTln/JF3G/xBk//8QZP//E2P3/y5Z + p/9LTlP/TU9O/0JnbbUrnKsVMY6cAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAABCZWsAO3eBVUtQUfxIXWH/LMno/yjc//8o2///KNv//yjb + //8o2///KNv//yjb//8o2///KNz//ynR8v8sxeP/KNb4/yjc//8o3P//KdLy/z96hP9OS0n/Q1Fq/xph + 5P8QZP//EGT//xFk/P8sWq3/S01S/0xRUf5AbHJ5pQAAAB660gAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAABDZGkAPXN7YEtQUf9HYmf/K83t/yjc + //8o2///KNv//yjb//8o2///KNv//yjb//8o3P//LMno/0F0ff9JWVz/OoiW/yjV9/8o2///KN3//yzE + 4f9GY2j/TkxJ/zFXnv8SZPz/FWLy/xdh7P8YYej/OFWK/05MS/9HXF/QLJipFi2XpwAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAABDY2gAPXJ7YEtQ + Uf9HYWb/K83t/yjc//8o2///KNv//yjb//8o2///KNv//yjb//8n3f//NaW7/01MS/9OS0v/SlZY/y3B + 3v8o3f//KNv//yfd//82m67/TUxL/0dPYP86VIT/QlFu/0VQZf9EUGn/RVBk/01MTP9HWl3mL5OjJi6V + pQAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AABAanAAO3Z/RktSU/dKVln/Lr7a/yjd//8o2///KNv//yjb//8o2///KNv//yjb//8o3f//L7nU/0la + Xf9OSkr/Q2tz/yrN7f8o3P//KNv//yfd//83mKr/TUxM/01MTP9OTUv/TU9N/k1PTvpNT078TE9P/0tR + Uv9DZGmmJ6a5CC6UpAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAA4fYgAOH6JHElWWdhNTEz/N5Wm/yfc//8o2///KNv//yjb//8o2///KNv//yjb + //8o2///KNr9/zC30f83nrL/LcPg/yjb//8o2///KN3//yvI5v9FZm3/TUxL/0lXWe5DZGmsQmdsbUdb + XklCZ21aP210eTx0fGwwkZ8ePnB5AAzk/wAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAoo7cAAP//AUFobZZNTk7/R15i/y6+2f8n3f//KNv//yjb + //8o2///KNv//yjb//8o2///KNv//yjd//8n3f//KNz//yjb//8o3f//K8zs/0B4g/9NTEv/SVZY6zl7 + hlMP3PYFNYShAAD//wAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAOXyGADOKlzJGXGDgTktL/0Ns + dP8swt//J93//yjb//8o2///KNv//yjb//8o2///KNv//yjb//8o2///KNv//yfd//8sxeP/QXaA/01M + S/9KVFX5PnB3eAD//wIpoKwAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAG7/ZAAD/ + /wA9c3taSlNU605LS/9FZWv/Ma3F/yjX+f8n3f//KNz//yjb//8o2///KNv//yjc//8o3f//KNf5/zKt + xf9FZm3/TktK/0pVV/k9cXmGIbPHCSqdrQAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAADh8hgAfs8kBQWhuW0hYWulNTEv/S1NU/z97h/8yrcT/K8vq/yjX+f8n2v3/KNn8/yrQ + 8f8ws83/Pn6K/0tTVP9NTEv/SFhb6z1xem0cvdUJJaq+AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAfuMsAAf3/Ajl6hEFFX2TAS1FS+05LSv9MUFD/R2Fl/0F0 + ff89for/PnuH/0Vob/9LU1T/TktK/0tRUvxEYWbEN3+JRgnp/wMft8kAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAIrHIADp5gwAtl6cUPXJ6ZkZe + Yb1KVFbvTE5P/U1MTP9OS0r/TktK/0xOTv9LUlPzRl1gxz5vd2ssmKkWQmZsABjJ5AAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAA//8AMY2cACuaqww7dn8zQGtyZEZeYYBNTU2AS1JTgUBrcXc+cHg/MouZEAD//wAVzegAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA + AAD///////8AAP//AAP//wAA//AAAH//AAD/wAAAH/8AAP8AAAAH/wAA/gAAAAP/AAD8AAAAAP8AAPgA + AAAAfwAA8AAAAAA/AADgAAAAAD8AAOAAAAAAHwAAwAAAAAAfAADAAAAAAA8AAIAAAAAADwAAgAAAAAAP + AACAAAAAAA8AAAAAAAAADwAAAAAAAAAPAAAAAAAAAA8AAAAAAAAADwAAAAAAAAAfAAAAAAAAAB8AAAAA + AAAAHwAAAAAAAAA/AAAAAAAAAH8AAAAAAAAAfwAAAAAAAAD/AACAAAAAAf8AAIAA4AAD/wAAgAfAAAP/ + AACAH4AAAD8AAMB/gAAAHwAAwP8AAAAPAADD/wAAAAcAAP//AAAAAwAA//8AAAADAAD//wAAAAEAAP// + AAAAAQAA//8AAAABAAD//wAAAAMAAP//AAAA/wAA//+AAAH/AAD//8AAA/8AAP//wAAH/wAA///gAA// + AAD///gAP/8AAP///gD//wAA////////AAA= \ No newline at end of file diff --git a/Rubberduck.Core/UI/CodeExplorer/CodeExplorerControl.xaml b/Rubberduck.Core/UI/CodeExplorer/CodeExplorerControl.xaml index b62c1b162b..4d2a9a6861 100644 --- a/Rubberduck.Core/UI/CodeExplorer/CodeExplorerControl.xaml +++ b/Rubberduck.Core/UI/CodeExplorer/CodeExplorerControl.xaml @@ -264,7 +264,9 @@ - + @@ -340,7 +342,7 @@ - + diff --git a/Rubberduck.Core/UI/Command/MenuItems/CommandBars/SerializeProjectsCommandMenuItem.cs b/Rubberduck.Core/UI/Command/MenuItems/CommandBars/SerializeProjectsCommandMenuItem.cs index 2d735d64bb..aba8ecc57a 100644 --- a/Rubberduck.Core/UI/Command/MenuItems/CommandBars/SerializeProjectsCommandMenuItem.cs +++ b/Rubberduck.Core/UI/Command/MenuItems/CommandBars/SerializeProjectsCommandMenuItem.cs @@ -77,9 +77,9 @@ protected override void OnExecute(object parameter) _serializationProvider.SerializeProject(library); } -#if DEBUG - //This block must be inside a DEBUG block because the Serialize method - //called is conditionally compiled and available only for a DEBUG build. +#if TRACE_COM_SAFE + //This block must be inside a conditional compilation block because the Serialize method + //called is conditionally compiled and available only if the compilation constant TRACE_COM_SAFE is set. var path = !string.IsNullOrWhiteSpace(_serializationProvider.Target) ? Path.GetDirectoryName(_serializationProvider.Target) : Path.GetTempPath(); diff --git a/Rubberduck.Core/UI/Controls/ToolBar.xaml b/Rubberduck.Core/UI/Controls/ToolBar.xaml index c169313959..600eb64a50 100644 --- a/Rubberduck.Core/UI/Controls/ToolBar.xaml +++ b/Rubberduck.Core/UI/Controls/ToolBar.xaml @@ -5,6 +5,16 @@ + + + + + + + + + - - - - - - - - - - - + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + @@ -282,11 +98,15 @@ - + + + @@ -347,11 +167,15 @@ - + + + diff --git a/Rubberduck.Parsing/Grammar/Tokens.cs b/Rubberduck.Parsing/Grammar/Tokens.cs index 3767cda86a..251d0d98af 100644 --- a/Rubberduck.Parsing/Grammar/Tokens.cs +++ b/Rubberduck.Parsing/Grammar/Tokens.cs @@ -52,6 +52,19 @@ public static class Tokens public static readonly string Debug = "Debug"; public static readonly string Decimal = "Decimal"; public static readonly string Declare = "Declare"; + public static readonly string DefBool = "DefBool"; + public static readonly string DefByte = "DefByte"; + public static readonly string DefCur = "DefCur"; + public static readonly string DefDate = "DefDate"; + public static readonly string DefDbl = "DefDbl"; + public static readonly string DefInt = "DefInt"; + public static readonly string DefLng = "DefLng"; + public static readonly string DefLngLng = "DefLngLng"; + public static readonly string DefLngPtr = "DefLngptr"; + public static readonly string DefObj = "DefObj"; + public static readonly string DefSng = "DefSng"; + public static readonly string DefStr = "DefStr"; + public static readonly string DefVar = "DefVar"; public static readonly string Dim = "Dim"; public static readonly string Dir = "Dir"; public static readonly string Do = "Do"; @@ -66,8 +79,10 @@ public static class Tokens public static readonly string Environ = "Environ"; public static readonly string EOF = "EOF"; public static readonly string Eqv = "Eqv"; + public static readonly string Erase = "Erase"; public static readonly string Err = "Err"; public static readonly string Error = "Error"; + public static readonly string Event = "Event"; public static readonly string Exit = "Exit"; public static readonly string Exp = "Exp"; public static readonly string Explicit = "Explicit"; @@ -111,11 +126,13 @@ public static class Tokens public static readonly string Like = "Like"; public static readonly string Line = "Line"; public static readonly string LineContinuation = " _"; + public static readonly string Lock = "Lock"; public static readonly string LOF = "LOF"; public static readonly string Long = "Long"; public static readonly string LongLong = "LongLong"; public static readonly string LongPtr = "LongPtr"; public static readonly string Loop = "Loop"; + public static readonly string LSet = "LSet"; public static readonly string LTrim = "LTrim"; public static readonly string Me = "Me"; public static readonly string Mid = "Mid"; @@ -146,6 +163,7 @@ public static class Tokens public static readonly string Property = "Property"; public static readonly string Public = "Public"; public static readonly string Put = "Put"; + public static readonly string RaiseEvent = "RaiseEvent"; public static readonly string Random = "Random"; public static readonly string Randomize = "Randomize"; public static readonly string Read = "Read"; @@ -153,14 +171,17 @@ public static class Tokens public static readonly string Rem = "Rem"; public static readonly string Resume = "Resume"; public static readonly string Return = "Return"; + public static readonly string RSet = "RSet"; public static readonly string Right = "Right"; public static readonly string RightB = "RightB"; public static readonly string RmDir = "RmDir"; public static readonly string Rnd = "Rnd"; public static readonly string RTrim = "RTrim"; public static readonly string Second = "Second"; + public static readonly string Seek = "Seek"; public static readonly string Select = "Select"; public static readonly string Set = "Set"; + public static readonly string Shared = "Shared"; public static readonly string Shell = "Shell"; public static readonly string Sin = "Sin"; public static readonly string Single = "Single"; @@ -187,6 +208,7 @@ public static class Tokens public static readonly string TypeOf = "TypeOf"; public static readonly string UBound = "UBound"; public static readonly string UCase = "UCase"; + public static readonly string Unlock = "Unlock"; public static readonly string Until = "Until"; public static readonly string Val = "Val"; public static readonly string Variant = "Variant"; @@ -205,6 +227,7 @@ public static class Tokens public static readonly string While = "While"; public static readonly string Width = "Width"; public static readonly string With = "With"; + public static readonly string WithEvents = "WithEvents"; public static readonly string Write = "Write"; public static readonly string XOr = "Xor"; public static readonly string Year = "Year"; diff --git a/Rubberduck.Parsing/Inspections/Abstract/IQuickFixProvider.cs b/Rubberduck.Parsing/Inspections/Abstract/IQuickFixProvider.cs index bef2b57611..75d2cf8149 100644 --- a/Rubberduck.Parsing/Inspections/Abstract/IQuickFixProvider.cs +++ b/Rubberduck.Parsing/Inspections/Abstract/IQuickFixProvider.cs @@ -9,6 +9,8 @@ namespace Rubberduck.Parsing.Inspections.Abstract /// public interface IQuickFixProvider { + IEnumerable QuickFixes(Type inspectionType); + IEnumerable QuickFixes(IInspectionResult result); void Fix(IQuickFix fix, IInspectionResult result); diff --git a/Rubberduck.Parsing/Inspections/CannotAnnotateAttribute.cs b/Rubberduck.Parsing/Inspections/CannotAnnotateAttribute.cs index 61ceaabcb7..7fc45b77be 100644 --- a/Rubberduck.Parsing/Inspections/CannotAnnotateAttribute.cs +++ b/Rubberduck.Parsing/Inspections/CannotAnnotateAttribute.cs @@ -9,4 +9,15 @@ namespace Rubberduck.Parsing.Inspections public class CannotAnnotateAttribute : Attribute { } + + [AttributeUsage(AttributeTargets.Class, AllowMultiple = true)] + public class QuickFixAttribute : Attribute + { + public QuickFixAttribute(Type quickFixType) + { + QuickFixType = quickFixType; + } + + public Type QuickFixType { get; } + } } \ No newline at end of file diff --git a/Rubberduck.Resources/Experimentals/ExperimentalNames.cs.resx b/Rubberduck.Resources/Experimentals/ExperimentalNames.cs.resx new file mode 100644 index 0000000000..2757c9c37d --- /dev/null +++ b/Rubberduck.Resources/Experimentals/ExperimentalNames.cs.resx @@ -0,0 +1,123 @@ + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + text/microsoft-resx + + + 2.0 + + + System.Resources.ResXResourceReader, System.Windows.Forms, Version=4.0.0.0, Culture=neutral, PublicKeyToken=b77a5c561934e089 + + + System.Resources.ResXResourceWriter, System.Windows.Forms, Version=4.0.0.0, Culture=neutral, PublicKeyToken=b77a5c561934e089 + + + Inspekce označují prázdné bloky, které jsou chráněny booleovským výrazem + + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs b/Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs index 6f20bd648e..9caa412a25 100644 --- a/Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs +++ b/Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs @@ -591,6 +591,15 @@ public class InspectionInfo { } } + /// + /// Looks up a localized string similar to 'While...Wend' loops exist for backward compatibility and have been superseded by the introduction of 'Do While...Loop' blocks, which support the 'Exit Do' exit statement. 'While...Wend' loops cannot be exited other than fulfilling the 'While' condition.. + /// + public static string ObsoleteWhileWendStatementInspection { + get { + return ResourceManager.GetString("ObsoleteWhileWendStatementInspection", resourceCulture); + } + } + /// /// Looks up a localized string similar to While this is legal, this is poorly documented "feature" that means something different -- the error state is also cleared in addition to disabling any error handling. However, this can be ambiguous as a negative line label of -1 may end up as a target and excessively complex error handling usually indicates a need of refactoring the procedure.. /// diff --git a/Rubberduck.Resources/Inspections/InspectionInfo.cs.resx b/Rubberduck.Resources/Inspections/InspectionInfo.cs.resx index e67a2598f4..49ab738c92 100644 --- a/Rubberduck.Resources/Inspections/InspectionInfo.cs.resx +++ b/Rubberduck.Resources/Inspections/InspectionInfo.cs.resx @@ -379,4 +379,7 @@ Jestliže může být parametr prázdný, ignorujte výsledek této inspekce; p I když je tato "funkce" legální, je velmi špatně zdokumentována a dělá něco úplně jiného -- chybový stav je také vyčištěn a ještě k tomu je vypnuto jakékoli řešení chyb. Toto může být nejednoznačné, protože záporný řádek -1 může skončit jako cíl pro nadměrně složité zpracování chyb, které většinou potřebuje refaktorování procedury. + + Smyčky 'While...Wend' existují pro zpětnou kompatibilitu a byly nahrazeny zavedením bloků 'Do While...Loop', které podporují příkaz 'Exit Do'. Smyčky 'While...Wend' nelze ukončit jinak než splněním podmínky 'While'. + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/InspectionInfo.fr.resx b/Rubberduck.Resources/Inspections/InspectionInfo.fr.resx index 05ac82e648..f49193cdb3 100644 --- a/Rubberduck.Resources/Inspections/InspectionInfo.fr.resx +++ b/Rubberduck.Resources/Inspections/InspectionInfo.fr.resx @@ -379,4 +379,7 @@ Si le paramètre peut être nul, ignorer ce résultat; passer une valeur nulle Bien que légale, cette syntaxe a un effet peu documentée -- toute erreur courante est supprimée, en plus de désactiver la gestion d'erreurs. L'instruction peut également être ambiguë, si la procédure contient effectivement une ligne -1. La stratégie de gestion d'erreurs semble plus complexe que nécessaire et pourrait être à revoir. + + Les boucles 'While...Wend' existent pour compatibilité avec les anciennes versions de VB, et ont été remplaçées par l'introduction des structures itératives 'Do While...Loop', qui supportent l'instruction 'Exit Do'. Les boucles 'While...Wend' ne peuvent être terminées qu'en remplissant la condition de l'expression 'While'. + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/InspectionInfo.resx b/Rubberduck.Resources/Inspections/InspectionInfo.resx index 033e1c041d..797f11c6ee 100644 --- a/Rubberduck.Resources/Inspections/InspectionInfo.resx +++ b/Rubberduck.Resources/Inspections/InspectionInfo.resx @@ -379,4 +379,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu While this is legal, this is poorly documented "feature" that means something different -- the error state is also cleared in addition to disabling any error handling. However, this can be ambiguous as a negative line label of -1 may end up as a target and excessively complex error handling usually indicates a need of refactoring the procedure. + + 'While...Wend' loops exist for backward compatibility and have been superseded by the introduction of 'Do While...Loop' blocks, which support the 'Exit Do' exit statement. 'While...Wend' loops cannot be exited other than fulfilling the 'While' condition. + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/InspectionNames.Designer.cs b/Rubberduck.Resources/Inspections/InspectionNames.Designer.cs index 59020fb39d..39790287cb 100644 --- a/Rubberduck.Resources/Inspections/InspectionNames.Designer.cs +++ b/Rubberduck.Resources/Inspections/InspectionNames.Designer.cs @@ -591,6 +591,15 @@ public class InspectionNames { } } + /// + /// Looks up a localized string similar to Use of obsolete 'While...Wend' statement. + /// + public static string ObsoleteWhileWendStatementInspection { + get { + return ResourceManager.GetString("ObsoleteWhileWendStatementInspection", resourceCulture); + } + } + /// /// Looks up a localized string similar to ThunderCode 101. /// diff --git a/Rubberduck.Resources/Inspections/InspectionNames.cs.resx b/Rubberduck.Resources/Inspections/InspectionNames.cs.resx index f74e5e78bc..9bfe97b571 100644 --- a/Rubberduck.Resources/Inspections/InspectionNames.cs.resx +++ b/Rubberduck.Resources/Inspections/InspectionNames.cs.resx @@ -378,4 +378,7 @@ ThunderCode 1 + + Použití zastaralého příkazu 'While...Wend' + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/InspectionNames.fr.resx b/Rubberduck.Resources/Inspections/InspectionNames.fr.resx index 9debdd2048..560c635387 100644 --- a/Rubberduck.Resources/Inspections/InspectionNames.fr.resx +++ b/Rubberduck.Resources/Inspections/InspectionNames.fr.resx @@ -349,7 +349,7 @@ Utilisation d'un membre marqué '@Obsolete' - Instruction 'On Local Error' + Instruction obsolète 'On Local Error' Caractère de soulignement dans le nom d'un membre d'un module de classe @@ -363,4 +363,7 @@ Annotation manquante (module) + + Utilisation de l'instruction obsolète 'While...Wend' + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/InspectionNames.resx b/Rubberduck.Resources/Inspections/InspectionNames.resx index 792f389f1f..386290b4a7 100644 --- a/Rubberduck.Resources/Inspections/InspectionNames.resx +++ b/Rubberduck.Resources/Inspections/InspectionNames.resx @@ -383,4 +383,7 @@ ThunderCode 101 meta easter egg; do not translate + + Use of obsolete 'While...Wend' statement + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/InspectionResults.Designer.cs b/Rubberduck.Resources/Inspections/InspectionResults.Designer.cs index 30811c303e..f1db10907c 100644 --- a/Rubberduck.Resources/Inspections/InspectionResults.Designer.cs +++ b/Rubberduck.Resources/Inspections/InspectionResults.Designer.cs @@ -609,6 +609,15 @@ public class InspectionResults { } } + /// + /// Looks up a localized string similar to 'While...Wend' conditional loop can be written as a 'Do While...Loop' block.. + /// + public static string ObsoleteWhileWendStatementInspection { + get { + return ResourceManager.GetString("ObsoleteWhileWendStatementInspection", resourceCulture); + } + } + /// /// Looks up a localized string similar to On Error GoTo -1 encountered. /// diff --git a/Rubberduck.Resources/Inspections/InspectionResults.cs.resx b/Rubberduck.Resources/Inspections/InspectionResults.cs.resx index 1b6a831f75..6f769c8a6a 100644 --- a/Rubberduck.Resources/Inspections/InspectionResults.cs.resx +++ b/Rubberduck.Resources/Inspections/InspectionResults.cs.resx @@ -399,4 +399,7 @@ In memoriam, 1972-2018 Pevná mezera v identifikátoru '{0}' + + Bloková odmínka 'While...Wend' může být napsána jako 'Do While...Loop'. + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/InspectionResults.fr.resx b/Rubberduck.Resources/Inspections/InspectionResults.fr.resx index e3c2f8d2f2..e3aa5843c9 100644 --- a/Rubberduck.Resources/Inspections/InspectionResults.fr.resx +++ b/Rubberduck.Resources/Inspections/InspectionResults.fr.resx @@ -402,4 +402,7 @@ In memoriam, 1972-2018 Le nom du membre '{0}' est un mot-clé + + La boucle conditionelle 'While...Wend' pourrait être 'Do While...Loop' + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/InspectionResults.resx b/Rubberduck.Resources/Inspections/InspectionResults.resx index 28e481ba77..c3d0944518 100644 --- a/Rubberduck.Resources/Inspections/InspectionResults.resx +++ b/Rubberduck.Resources/Inspections/InspectionResults.resx @@ -422,4 +422,7 @@ In memoriam, 1972-2018 On Error GoTo -1 encountered + + 'While...Wend' conditional loop can be written as a 'Do While...Loop' block. + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/QuickFixes.Designer.cs b/Rubberduck.Resources/Inspections/QuickFixes.Designer.cs index 74975f3316..234c7820db 100644 --- a/Rubberduck.Resources/Inspections/QuickFixes.Designer.cs +++ b/Rubberduck.Resources/Inspections/QuickFixes.Designer.cs @@ -483,6 +483,15 @@ public class QuickFixes { } } + /// + /// Looks up a localized string similar to Replace 'While...Wend' with 'Do While...Loop'. + /// + public static string ReplaceWhileWendWithDoWhileLoopQuickFix { + get { + return ResourceManager.GetString("ReplaceWhileWendWithDoWhileLoopQuickFix", resourceCulture); + } + } + /// /// Looks up a localized string similar to Return explicit Variant. /// diff --git a/Rubberduck.Resources/Inspections/QuickFixes.cs.resx b/Rubberduck.Resources/Inspections/QuickFixes.cs.resx index 6610de0791..957cf040a8 100644 --- a/Rubberduck.Resources/Inspections/QuickFixes.cs.resx +++ b/Rubberduck.Resources/Inspections/QuickFixes.cs.resx @@ -288,4 +288,7 @@ Chyba Při Aplikování Rychlé Chyby + + Nahradit 'While...Wend' za 'Do While...Loop' + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/QuickFixes.fr.resx b/Rubberduck.Resources/Inspections/QuickFixes.fr.resx index 4b2eed2d6d..265c350ded 100644 --- a/Rubberduck.Resources/Inspections/QuickFixes.fr.resx +++ b/Rubberduck.Resources/Inspections/QuickFixes.fr.resx @@ -288,4 +288,7 @@ Un module affecté a été modifier depuis la dernière analyse. + + Remplacer 'While...Wend' par 'Do While...Loop' + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/QuickFixes.resx b/Rubberduck.Resources/Inspections/QuickFixes.resx index d992a0ed0a..02655ba302 100644 --- a/Rubberduck.Resources/Inspections/QuickFixes.resx +++ b/Rubberduck.Resources/Inspections/QuickFixes.resx @@ -288,4 +288,7 @@ Quick Fix Application Failure + + Replace 'While...Wend' with 'Do While...Loop' + \ No newline at end of file diff --git a/Rubberduck.Resources/RubberduckUI.Designer.cs b/Rubberduck.Resources/RubberduckUI.Designer.cs index 0fd25ba52a..fb032f8380 100644 --- a/Rubberduck.Resources/RubberduckUI.Designer.cs +++ b/Rubberduck.Resources/RubberduckUI.Designer.cs @@ -2202,7 +2202,7 @@ public class RubberduckUI { } /// - /// Looks up a localized string similar to The target '{0}'is already a field.. + /// Looks up a localized string similar to The target '{0}' is already a field.. /// public static string IntroduceFieldFailed_TargetIsAlreadyAField { get { @@ -2229,7 +2229,7 @@ public class RubberduckUI { } /// - /// Looks up a localized string similar to The target '{0}'is not contained in a method.. + /// Looks up a localized string similar to The target '{0}' is not contained in a method.. /// public static string IntroduceParameterFailed_TargetNotContainedInMethod { get { @@ -2441,7 +2441,7 @@ public class RubberduckUI { } /// - /// Looks up a localized string similar to The method using '{0}' already has the declaration '{1}'' of the same name in scope.. + /// Looks up a localized string similar to The method using '{0}' already has the declaration '{1}' of the same name in scope.. /// public static string MoveCloserToUsageFailure_ReferencingMethodHasSameNameDeclarationInScope { get { @@ -3651,7 +3651,7 @@ public class RubberduckUI { } /// - /// Looks up a localized string similar to Target control '{0}' not found,. + /// Looks up a localized string similar to Target control '{0}' not found.. /// public static string RenameFailure_TargetContriolNotFound { get { diff --git a/Rubberduck.Resources/RubberduckUI.cs.resx b/Rubberduck.Resources/RubberduckUI.cs.resx index 61927795e6..c21cecc5f5 100644 --- a/Rubberduck.Resources/RubberduckUI.cs.resx +++ b/Rubberduck.Resources/RubberduckUI.cs.resx @@ -373,7 +373,7 @@ Upozornění: Všechna uživatelská nastavení budou ztracena. Váš starý sou Získali jste odznak "Continuator"! - Nastavení modulu by měly být specifikovány jako první + Nastavení modulu by měla být specifikována jako první Rubberduck - Odstranit Parametry @@ -1355,6 +1355,45 @@ End Enum Filtr - Metoda používající '{0}' má již jinou deklaraci stejného jména v rozsahu. + Metoda používající '{0}' má již jinou deklaraci '{1}' stejného jména v rozsahu. + + + Refaktorování selhalo. + + + Neexistuje žádný aktivní výběr. + + + Vybraný cíl nejde refaktorovat. + + + Cílová deklarace je 'Null' + + + Nebyl vybrán žádný příkaz implementace. + + + Cílový control '{0}' nebyl nalezen. + + + Pro cílový modul '{0}' nebyl nalezen žádný kódový modul. + + + Cíl '{0}' je standardní ovladač událostí, který nemůže být přejmenován. + + + Cíl není uživatelsky definován. + + + Cíl '{0}' je již pole. + + + Cíl '{0}' není obsažen v metodě. + + + Deklarace typu cíle '{0}' je '{1}' namísto očekávaného '{2}'. + + + Typ deklarace cíle '{0}' je '{1}' namísto jednoho z očekávaných '{2}'. \ No newline at end of file diff --git a/Rubberduck.Resources/RubberduckUI.resx b/Rubberduck.Resources/RubberduckUI.resx index 99f14d1ee6..1ffa4a2d34 100644 --- a/Rubberduck.Resources/RubberduckUI.resx +++ b/Rubberduck.Resources/RubberduckUI.resx @@ -1513,7 +1513,7 @@ NOTE: Restart is required for the setting to take effect. {0}: Variable Name - The method using '{0}' already has the declaration '{1}'' of the same name in scope. + The method using '{0}' already has the declaration '{1}' of the same name in scope. {0}: Variable Name; {1}: name of conflicting declaration @@ -1564,7 +1564,7 @@ NOTE: Restart is required for the setting to take effect. {0}: name of module - Target control '{0}' not found, + Target control '{0}' not found. {0}: name of control @@ -1583,11 +1583,11 @@ NOTE: Restart is required for the setting to take effect. No implements selected. - The target '{0}'is already a field. + The target '{0}' is already a field. {0}: name of target - The target '{0}'is not contained in a method. + The target '{0}' is not contained in a method. {0}: name of target diff --git a/Rubberduck.Resources/Settings/SettingsUI.cs.resx b/Rubberduck.Resources/Settings/SettingsUI.cs.resx index 58484d6da2..2ea3cc0628 100644 --- a/Rubberduck.Resources/Settings/SettingsUI.cs.resx +++ b/Rubberduck.Resources/Settings/SettingsUI.cs.resx @@ -175,7 +175,7 @@ Rubberduck Nastavení - Nastavení Aplikace + Nastavení Automatického Doplňování Načíst Obecná Nastavení diff --git a/Rubberduck.Resources/Settings/UnitTestingPage.cs.resx b/Rubberduck.Resources/Settings/UnitTestingPage.cs.resx index 744991c190..a1aaa6d2e5 100644 --- a/Rubberduck.Resources/Settings/UnitTestingPage.cs.resx +++ b/Rubberduck.Resources/Settings/UnitTestingPage.cs.resx @@ -127,10 +127,10 @@ Typ zabezpečení: - Binding mód: + Režim vazby (binding): - Časný binding + Časná vazba Inicializace/úklid test metody @@ -142,7 +142,7 @@ Inicializace/úklid test modulu - Pozdní binding + Pozdní vazba Tolerantní assert diff --git a/Rubberduck.Resources/Templates.cs.resx b/Rubberduck.Resources/Templates.cs.resx index 4b2b5c988e..2bd9f3b38e 100644 --- a/Rubberduck.Resources/Templates.cs.resx +++ b/Rubberduck.Resources/Templates.cs.resx @@ -127,18 +127,7 @@ Přidá modul třídy, který je předdeklarovaný a může být tedy použit bez nutnosti do něj napsat hlavičku. - VERSION 1.0 CLASS -BEGIN - MultiUse = -1 'True -END -Attribute VB_GlobalNameSpace = False -Attribute VB_Creatable = False -Attribute VB_PredeclaredId = True -Attribute VB_Exposed = False -Attribute VB_Ext_KEY = "Rubberduck", "Predeclared Class Module" - -Option Explicit -'@PredeclaredId + Do not translate \ No newline at end of file diff --git a/Rubberduck.Resources/UnitTesting/AssertMessages.cs.resx b/Rubberduck.Resources/UnitTesting/AssertMessages.cs.resx index 0f6c235bdf..25c28d7610 100644 --- a/Rubberduck.Resources/UnitTesting/AssertMessages.cs.resx +++ b/Rubberduck.Resources/UnitTesting/AssertMessages.cs.resx @@ -205,7 +205,7 @@ Rubberduck nebyl schopen zpracovat výsledky volání. - Reference, které Rubberduck potřebuje pro early-binding testy, nemůžou být vyřešeny. Je možné, že jsou poškozeny. + Reference, které Rubberduck potřebuje pro testy časných-vazeb, nemůžou být vyřešeny. Je možné, že jsou poškozeny. Při běhu testů se vyskytla neočekávaná COM výjimka. diff --git a/Rubberduck.SettingsProvider/Persistence/XmlPersistenceService.cs b/Rubberduck.SettingsProvider/Persistence/XmlPersistenceService.cs index 8fb8260ef2..8d850b5c1a 100644 --- a/Rubberduck.SettingsProvider/Persistence/XmlPersistenceService.cs +++ b/Rubberduck.SettingsProvider/Persistence/XmlPersistenceService.cs @@ -62,7 +62,9 @@ protected override void Write(T toSerialize, string path) } } - using (var xml = XmlWriter.Create(FilePath, OutputXmlSettings)) + EnsurePathExists(filePath); + + using (var xml = XmlWriter.Create(filePath, OutputXmlSettings)) { doc.WriteTo(xml); } diff --git a/Rubberduck.VBEEditor/ComManagement/ComSafeBase.cs b/Rubberduck.VBEEditor/ComManagement/ComSafeBase.cs index 52b48626bc..367704f043 100644 --- a/Rubberduck.VBEEditor/ComManagement/ComSafeBase.cs +++ b/Rubberduck.VBEEditor/ComManagement/ComSafeBase.cs @@ -32,7 +32,7 @@ public void Dispose() protected virtual void Dispose(bool disposing) { -#if DEBUG +#if TRACE_COM_SAFE if (_disposed) { return; @@ -70,7 +70,7 @@ protected virtual void Dispose(bool disposing) #endif } -#if DEBUG +#if TRACE_COM_SAFE private struct TraceData { internal int HashCode { get; set; } diff --git a/Rubberduck.VBEEditor/ComManagement/IComSafe.cs b/Rubberduck.VBEEditor/ComManagement/IComSafe.cs index 1cde0699fe..13a8b44e0b 100644 --- a/Rubberduck.VBEEditor/ComManagement/IComSafe.cs +++ b/Rubberduck.VBEEditor/ComManagement/IComSafe.cs @@ -7,9 +7,9 @@ public interface IComSafe: IDisposable { void Add(ISafeComWrapper comWrapper); bool TryRemove(ISafeComWrapper comWrapper); -#if DEBUG +#if TRACE_COM_SAFE /// - /// Available in DEBUG build only. Provide a mechanism for serializing both + /// Available only if the compilation constant TRACE_COM_SAFE is set. Provide a mechanism for serializing both /// a snapshot of the COM safe at the instant and a historical activity log /// with a limited stack trace for each entry. /// diff --git a/Rubberduck.VBEEditor/ComManagement/StrongComSafe.cs b/Rubberduck.VBEEditor/ComManagement/StrongComSafe.cs index fa1e19b03f..d979ad98f3 100644 --- a/Rubberduck.VBEEditor/ComManagement/StrongComSafe.cs +++ b/Rubberduck.VBEEditor/ComManagement/StrongComSafe.cs @@ -1,8 +1,11 @@ using System.Collections.Concurrent; -using System.Collections.Generic; -using System.Linq; using Rubberduck.VBEditor.SafeComWrappers.Abstract; +#if TRACE_COM_SAFE +using System.Linq; +using System.Collections.Generic; +#endif + namespace Rubberduck.VBEditor.ComManagement { public class StrongComSafe: ComSafeBase @@ -19,14 +22,14 @@ public override void Add(ISafeComWrapper comWrapper) comWrapper, key => { -#if DEBUG +#if TRACE_COM_SAFE TraceAdd(comWrapper); #endif return 1; }, (key, value) => { -#if DEBUG +#if TRACE_COM_SAFE TraceUpdate(comWrapper); #endif return value; @@ -42,7 +45,7 @@ public override bool TryRemove(ISafeComWrapper comWrapper) } var result = _comWrapperCache.TryRemove(comWrapper, out _); -#if DEBUG +#if TRACE_COM_SAFE TraceRemove(comWrapper, result); #endif return result; @@ -67,7 +70,7 @@ protected override void Dispose(bool disposing) _comWrapperCache.Clear(); } -#if DEBUG +#if TRACE_COM_SAFE protected override IDictionary GetWrappers() { return _comWrapperCache.Keys.ToDictionary(GetComWrapperObjectHashCode); diff --git a/Rubberduck.VBEEditor/ComManagement/WeakComSafe.cs b/Rubberduck.VBEEditor/ComManagement/WeakComSafe.cs index 54200ffb86..d74b3aa58f 100644 --- a/Rubberduck.VBEEditor/ComManagement/WeakComSafe.cs +++ b/Rubberduck.VBEEditor/ComManagement/WeakComSafe.cs @@ -1,10 +1,10 @@ using System; using System.Collections.Concurrent; -using System.Collections.Generic; using Rubberduck.VBEditor.SafeComWrappers.Abstract; -#if DEBUG +#if TRACE_COM_SAFE using System.Linq; +using System.Collections.Generic; #endif namespace Rubberduck.VBEditor.ComManagement @@ -22,14 +22,14 @@ public override void Add(ISafeComWrapper comWrapper) GetComWrapperObjectHashCode(comWrapper), key => { -#if DEBUG +#if TRACE_COM_SAFE TraceAdd(comWrapper); #endif return (DateTime.UtcNow, new WeakReference(comWrapper)); }, (key, value) => { -#if DEBUG +#if TRACE_COM_SAFE TraceUpdate(comWrapper); #endif return (value.insertTime, new WeakReference(comWrapper)); @@ -46,7 +46,7 @@ public override bool TryRemove(ISafeComWrapper comWrapper) } var result = _comWrapperCache.TryRemove(GetComWrapperObjectHashCode(comWrapper), out _); -#if DEBUG +#if TRACE_COM_SAFE TraceRemove(comWrapper, result); #endif return result; @@ -74,7 +74,7 @@ protected override void Dispose(bool disposing) _comWrapperCache.Clear(); } -#if DEBUG +#if TRACE_COM_SAFE protected override IDictionary GetWrappers() { var dictionary = new Dictionary(); diff --git a/Rubberduck.VBEEditor/SourceCodeHandling/SourceFileHandlerComponentSourceCodeHandlerAdapter.cs b/Rubberduck.VBEEditor/SourceCodeHandling/SourceFileHandlerComponentSourceCodeHandlerAdapter.cs index b122d031f1..e8e09ca12f 100644 --- a/Rubberduck.VBEEditor/SourceCodeHandling/SourceFileHandlerComponentSourceCodeHandlerAdapter.cs +++ b/Rubberduck.VBEEditor/SourceCodeHandling/SourceFileHandlerComponentSourceCodeHandlerAdapter.cs @@ -1,4 +1,5 @@ using System.IO; +using System.Text; using Rubberduck.VBEditor.SafeComWrappers; using Rubberduck.VBEditor.SafeComWrappers.Abstract; @@ -31,7 +32,7 @@ public IVBComponent SubstituteCode(IVBComponent module, string newCode) { return module; } - File.WriteAllText(fileName, newCode); + File.WriteAllText(fileName, newCode, Encoding.Default); return _tempSourceFileHandler.ImportAndCleanUp(module, fileName); } } diff --git a/RubberduckCodeAnalysis/ComVisibleTypeAnalyzer.cs b/RubberduckCodeAnalysis/ComVisibleTypeAnalyzer.cs index 14b698ac92..eb20856c0f 100644 --- a/RubberduckCodeAnalysis/ComVisibleTypeAnalyzer.cs +++ b/RubberduckCodeAnalysis/ComVisibleTypeAnalyzer.cs @@ -7,6 +7,7 @@ namespace RubberduckCodeAnalysis { + [DiagnosticAnalyzer(LanguageNames.CSharp)] public class ComVisibleTypeAnalyzer : DiagnosticAnalyzer { diff --git a/RubberduckCodeAnalysis/InspectionXmlDocAnalyzer.cs b/RubberduckCodeAnalysis/InspectionXmlDocAnalyzer.cs new file mode 100644 index 0000000000..879f4e3800 --- /dev/null +++ b/RubberduckCodeAnalysis/InspectionXmlDocAnalyzer.cs @@ -0,0 +1,157 @@ +using System.Collections.Generic; +using System.Collections.Immutable; +using System.Linq; +using System.Xml.Linq; +using Microsoft.CodeAnalysis; +using Microsoft.CodeAnalysis.Diagnostics; + +namespace RubberduckCodeAnalysis +{ + [DiagnosticAnalyzer(LanguageNames.CSharp)] + public class InspectionXmlDocAnalyzer : DiagnosticAnalyzer + { + private const string MissingInspectionSummaryTag = "MissingInspectionSummaryTag"; + private static readonly DiagnosticDescriptor MissingSummaryTagRule = new DiagnosticDescriptor( + MissingInspectionSummaryTag, + new LocalizableResourceString(nameof(Resources.MissingInspectionSummaryTag), Resources.ResourceManager, typeof(Resources)), + new LocalizableResourceString(nameof(Resources.MissingInspectionSummaryTagMessageFormat), Resources.ResourceManager, typeof(Resources)), + new LocalizableResourceString(nameof(Resources.XmlDocAnalyzerCategory), Resources.ResourceManager, typeof(Resources)).ToString(), + DiagnosticSeverity.Error, + true, + new LocalizableResourceString(nameof(Resources.MissingInspectionSummaryTagDescription), Resources.ResourceManager, typeof(Resources)) + ); + + private const string MissingInspectionWhyTag = "MissingInspectionWhyTag"; + private static readonly DiagnosticDescriptor MissingWhyTagRule = new DiagnosticDescriptor( + MissingInspectionWhyTag, + new LocalizableResourceString(nameof(Resources.MissingInspectionWhyTag), Resources.ResourceManager, typeof(Resources)), + new LocalizableResourceString(nameof(Resources.MissingInspectionWhyTagMessageFormat), Resources.ResourceManager, typeof(Resources)), + new LocalizableResourceString(nameof(Resources.XmlDocAnalyzerCategory), Resources.ResourceManager, typeof(Resources)).ToString(), + DiagnosticSeverity.Error, + true, + new LocalizableResourceString(nameof(Resources.MissingInspectionWhyTagDescription), Resources.ResourceManager, typeof(Resources)) + ); + + private const string MissingReferenceTag = "MissingReferenceTag"; + private static readonly DiagnosticDescriptor MissingReferenceTagRule = new DiagnosticDescriptor( + MissingReferenceTag, + new LocalizableResourceString(nameof(Resources.MissingInspectionReferenceTag), Resources.ResourceManager, typeof(Resources)), + new LocalizableResourceString(nameof(Resources.MissingInspectionReferenceTagMessageFormat), Resources.ResourceManager, typeof(Resources)), + new LocalizableResourceString(nameof(Resources.XmlDocAnalyzerCategory), Resources.ResourceManager, typeof(Resources)).ToString(), + DiagnosticSeverity.Error, + true, + new LocalizableResourceString(nameof(Resources.MissingInspectionReferenceTagDescription), Resources.ResourceManager, typeof(Resources)) + ); + + private const string MissingRequiredLibraryAttribute = "MissingRequiredLibraryAttribute"; + private static readonly DiagnosticDescriptor MissingRequiredLibAttributeRule = new DiagnosticDescriptor( + MissingRequiredLibraryAttribute, + new LocalizableResourceString(nameof(Resources.MissingRequiredLibAttribute), Resources.ResourceManager, typeof(Resources)), + new LocalizableResourceString(nameof(Resources.MissingRequiredLibAttributeMessageFormat), Resources.ResourceManager, typeof(Resources)), + new LocalizableResourceString(nameof(Resources.XmlDocAnalyzerCategory), Resources.ResourceManager, typeof(Resources)).ToString(), + DiagnosticSeverity.Error, + true, + new LocalizableResourceString(nameof(Resources.MissingRequiredLibAttributeDescription), Resources.ResourceManager, typeof(Resources)) + ); + + private const string MissingExampleTag = "MissingExampleTag"; + private static readonly DiagnosticDescriptor MissingExampleTagRule = new DiagnosticDescriptor( + MissingExampleTag, + new LocalizableResourceString(nameof(Resources.MissingExampleTag), Resources.ResourceManager, typeof(Resources)), + new LocalizableResourceString(nameof(Resources.MissingExampleTagMessageFormat), Resources.ResourceManager, typeof(Resources)), + new LocalizableResourceString(nameof(Resources.XmlDocAnalyzerCategory), Resources.ResourceManager, typeof(Resources)).ToString(), + DiagnosticSeverity.Warning, + true, + new LocalizableResourceString(nameof(Resources.MissingExampleTagDescription), Resources.ResourceManager, typeof(Resources)) + ); + + public override ImmutableArray SupportedDiagnostics => + ImmutableArray.Create(MissingSummaryTagRule, MissingWhyTagRule, MissingReferenceTagRule, MissingRequiredLibAttributeRule); + + public override void Initialize(AnalysisContext context) + { + context.RegisterSymbolAction(AnalyzeSymbol, SymbolKind.NamedType); + } + + private static void AnalyzeSymbol(SymbolAnalysisContext context) + { + var namedTypeSymbol = (INamedTypeSymbol)context.Symbol; + if (!IsInspectionClass(namedTypeSymbol)) + { + return; + } + + var xml = XDocument.Load(namedTypeSymbol.GetDocumentationCommentXml()); + + CheckSummaryTag(context, namedTypeSymbol, xml); + CheckWhyTag(context, namedTypeSymbol, xml); + CheckExampleTag(context, namedTypeSymbol, xml); + + var requiredLibraryAttributes = namedTypeSymbol.GetAttributes().Where(a => a.AttributeClass.Name == "RequiredLibraryAttribute").ToList(); + CheckReferenceTag(context, namedTypeSymbol, xml, requiredLibraryAttributes); + CheckRequiredLibAttribute(context, namedTypeSymbol, xml, requiredLibraryAttributes); + } + + private static bool IsInspectionClass(INamedTypeSymbol namedTypeSymbol) + { + return namedTypeSymbol.TypeKind == TypeKind.Class && !namedTypeSymbol.IsAbstract + && namedTypeSymbol.ContainingNamespace.Name.StartsWith("Rubberduck.CodeAnalysis.Inspections.Concrete") + && namedTypeSymbol.AllInterfaces.Any(i => i.Name == "IInspection"); + } + + private static void CheckSummaryTag(SymbolAnalysisContext context, INamedTypeSymbol symbol, XDocument xml) + { + if (xml.Element("summary") == null) + { + var diagnostic = Diagnostic.Create(MissingSummaryTagRule, symbol.Locations[0], symbol.Name); + context.ReportDiagnostic(diagnostic); + } + } + + private static void CheckWhyTag(SymbolAnalysisContext context, INamedTypeSymbol symbol, XDocument xml) + { + if (xml.Element("why") == null) + { + var diagnostic = Diagnostic.Create(MissingWhyTagRule, symbol.Locations[0], symbol.Name); + context.ReportDiagnostic(diagnostic); + } + } + + private static void CheckReferenceTag(SymbolAnalysisContext context, INamedTypeSymbol symbol, XDocument xml, IEnumerable requiredLibAttributes) + { + var xmlRefLibs = xml.Elements("reference").Select(e => e.Attribute("name")?.Value).ToList(); + foreach (var attribute in requiredLibAttributes) + { + var requiredLib = attribute.ConstructorArguments[0].Value.ToString(); + if (xmlRefLibs.All(lib => lib != requiredLib)) + { + var diagnostic = Diagnostic.Create(MissingReferenceTagRule, symbol.Locations[0], symbol.Name, requiredLib); + context.ReportDiagnostic(diagnostic); + } + } + } + + private static void CheckRequiredLibAttribute(SymbolAnalysisContext context, INamedTypeSymbol symbol, XDocument xml, IEnumerable requiredLibAttributes) + { + var requiredLibs = requiredLibAttributes.Select(a => a.ConstructorArguments[0].Value.ToString()).ToList(); + foreach (var element in xml.Elements("reference")) + { + var xmlRefLib = element.Attribute("name")?.Value; + if (xmlRefLib == null || requiredLibs.All(lib => lib != xmlRefLib)) + { + var diagnostic = Diagnostic.Create(MissingRequiredLibAttributeRule, symbol.Locations[0], symbol.Name, xmlRefLib); + context.ReportDiagnostic(diagnostic); + } + } + } + + private static void CheckExampleTag(SymbolAnalysisContext context, INamedTypeSymbol symbol, XDocument xml) + { + if (!xml.Elements("example").Any()) + { + var diagnostic = Diagnostic.Create(MissingExampleTagRule, symbol.Locations[0], symbol.Name); + context.ReportDiagnostic(diagnostic); + } + } + } +} diff --git a/RubberduckCodeAnalysis/Resources.Designer.cs b/RubberduckCodeAnalysis/Resources.Designer.cs index 315b660007..15b32e72c9 100644 --- a/RubberduckCodeAnalysis/Resources.Designer.cs +++ b/RubberduckCodeAnalysis/Resources.Designer.cs @@ -22,7 +22,7 @@ namespace RubberduckCodeAnalysis { [global::System.CodeDom.Compiler.GeneratedCodeAttribute("System.Resources.Tools.StronglyTypedResourceBuilder", "15.0.0.0")] [global::System.Diagnostics.DebuggerNonUserCodeAttribute()] [global::System.Runtime.CompilerServices.CompilerGeneratedAttribute()] - internal class Resources { + public class Resources { private static global::System.Resources.ResourceManager resourceMan; @@ -36,7 +36,7 @@ internal class Resources { /// Returns the cached ResourceManager instance used by this class. /// [global::System.ComponentModel.EditorBrowsableAttribute(global::System.ComponentModel.EditorBrowsableState.Advanced)] - internal static global::System.Resources.ResourceManager ResourceManager { + public static global::System.Resources.ResourceManager ResourceManager { get { if (object.ReferenceEquals(resourceMan, null)) { global::System.Resources.ResourceManager temp = new global::System.Resources.ResourceManager("RubberduckCodeAnalysis.Resources", typeof(Resources).Assembly); @@ -51,7 +51,7 @@ internal class Resources { /// resource lookups using this strongly typed resource class. /// [global::System.ComponentModel.EditorBrowsableAttribute(global::System.ComponentModel.EditorBrowsableState.Advanced)] - internal static global::System.Globalization.CultureInfo Culture { + public static global::System.Globalization.CultureInfo Culture { get { return resourceCulture; } @@ -63,25 +63,25 @@ internal class Resources { /// /// Looks up a localized string similar to COM Management. /// - internal static string AnalyzerCategory { + public static string AnalyzerCategory { get { return ResourceManager.GetString("AnalyzerCategory", resourceCulture); } } /// - /// Looks up a localized string similar to Chained Wrappers. + /// Looks up a localized string similar to All types derived from SafeComWrappers should not be chained as it leaks unmanaged resources. Use an explicit local variable for each chained member.. /// - internal static string ChainedWrapperDescription { + public static string ChainedWrapperDescription { get { return ResourceManager.GetString("ChainedWrapperDescription", resourceCulture); } } /// - /// Looks up a localized string similar to Chained Wrappers. + /// Looks up a localized string similar to The type '{0}' derives from a SafeComWrapper base. It is called via other SafeComWrapper-derived type '{1}' in the expression '{2}'.. /// - internal static string ChainedWrapperMessageFormat { + public static string ChainedWrapperMessageFormat { get { return ResourceManager.GetString("ChainedWrapperMessageFormat", resourceCulture); } @@ -90,16 +90,16 @@ internal class Resources { /// /// Looks up a localized string similar to Chained Wrappers. /// - internal static string ChainedWrapperTitle { + public static string ChainedWrapperTitle { get { return ResourceManager.GetString("ChainedWrapperTitle", resourceCulture); } } /// - /// Looks up a localized string similar to COM-visible classes must have an explicit ClassInterface attribute and be set to `None`. This is required to avoid verisoning problems.. + /// Looks up a localized string similar to COM-visible classes must have an explicit ClassInterface attribute and be set to `None`. This is required to avoid versioning problems.. /// - internal static string MissingClassInterfaceDescription { + public static string MissingClassInterfaceDescription { get { return ResourceManager.GetString("MissingClassInterfaceDescription", resourceCulture); } @@ -108,7 +108,7 @@ internal class Resources { /// /// Looks up a localized string similar to MissingClassInterface. /// - internal static string MissingClassInterfaceId { + public static string MissingClassInterfaceId { get { return ResourceManager.GetString("MissingClassInterfaceId", resourceCulture); } @@ -117,7 +117,7 @@ internal class Resources { /// /// Looks up a localized string similar to COM-visible class '{0}' does not have an explicit ClassInterface attribute that is also set to 'ClassInterfaceType.None'.. /// - internal static string MissingClassInterfaceMessageFormat { + public static string MissingClassInterfaceMessageFormat { get { return ResourceManager.GetString("MissingClassInterfaceMessageFormat", resourceCulture); } @@ -126,7 +126,7 @@ internal class Resources { /// /// Looks up a localized string similar to Missing ClassInterface Attribute. /// - internal static string MissingClassInterfaceTitle { + public static string MissingClassInterfaceTitle { get { return ResourceManager.GetString("MissingClassInterfaceTitle", resourceCulture); } @@ -135,7 +135,7 @@ internal class Resources { /// /// Looks up a localized string similar to COM-visible classes must have an explicit ComDefaultInterface attribute referring to a COM-visible interface.. /// - internal static string MissingComDefaultInterfaceDescription { + public static string MissingComDefaultInterfaceDescription { get { return ResourceManager.GetString("MissingComDefaultInterfaceDescription", resourceCulture); } @@ -144,7 +144,7 @@ internal class Resources { /// /// Looks up a localized string similar to MissingComDefaultInterface. /// - internal static string MissingComDefaultInterfaceId { + public static string MissingComDefaultInterfaceId { get { return ResourceManager.GetString("MissingComDefaultInterfaceId", resourceCulture); } @@ -153,7 +153,7 @@ internal class Resources { /// /// Looks up a localized string similar to COM-visible class '{0}' must have an explicit ComDefaultInterface attribute using a typeof reference to a COM-visible interface. Do not use string to provide the interface name. . /// - internal static string MissingComDefaultInterfaceMessageFormat { + public static string MissingComDefaultInterfaceMessageFormat { get { return ResourceManager.GetString("MissingComDefaultInterfaceMessageFormat", resourceCulture); } @@ -162,16 +162,43 @@ internal class Resources { /// /// Looks up a localized string similar to Missing ComDefaultInterface Attribute. /// - internal static string MissingComDefaultInterfaceTitle { + public static string MissingComDefaultInterfaceTitle { get { return ResourceManager.GetString("MissingComDefaultInterfaceTitle", resourceCulture); } } + /// + /// Looks up a localized string similar to Missing xml-doc 'example' tag. + /// + public static string MissingExampleTag { + get { + return ResourceManager.GetString("MissingExampleTag", resourceCulture); + } + } + + /// + /// Looks up a localized string similar to Inspections xml-doc should have at least one 'example' tag, ideally two. If only one example is provided, website assumes the code example triggers the inspection. If two examples are provided, the second example is assumed to not trigger the inspection. Any further example is assumed to trigger the inspection.. + /// + public static string MissingExampleTagDescription { + get { + return ResourceManager.GetString("MissingExampleTagDescription", resourceCulture); + } + } + + /// + /// Looks up a localized string similar to XML documentation of type '{0}' has no <example> tag.. + /// + public static string MissingExampleTagMessageFormat { + get { + return ResourceManager.GetString("MissingExampleTagMessageFormat", resourceCulture); + } + } + /// /// Looks up a localized string similar to COM-visible types must have an explicit Guid attribute. This is required to avoid verisoning problems. Refer to RubberduckGuid constants.. /// - internal static string MissingGuidDescription { + public static string MissingGuidDescription { get { return ResourceManager.GetString("MissingGuidDescription", resourceCulture); } @@ -180,7 +207,7 @@ internal class Resources { /// /// Looks up a localized string similar to MissingGuid. /// - internal static string MissingGuidId { + public static string MissingGuidId { get { return ResourceManager.GetString("MissingGuidId", resourceCulture); } @@ -189,7 +216,7 @@ internal class Resources { /// /// Looks up a localized string similar to COM-visible type '{0}' does not have an explicit Guid attribute that references a RubberduckGuid constant.. /// - internal static string MissingGuidMessageFormat { + public static string MissingGuidMessageFormat { get { return ResourceManager.GetString("MissingGuidMessageFormat", resourceCulture); } @@ -198,16 +225,97 @@ internal class Resources { /// /// Looks up a localized string similar to Missing Guid Attribute. /// - internal static string MissingGuidTitle { + public static string MissingGuidTitle { get { return ResourceManager.GetString("MissingGuidTitle", resourceCulture); } } + /// + /// Looks up a localized string similar to Missing xml-doc 'reference' tag. + /// + public static string MissingInspectionReferenceTag { + get { + return ResourceManager.GetString("MissingInspectionReferenceTag", resourceCulture); + } + } + + /// + /// Looks up a localized string similar to XML documentation for inspections with a [RequiredLibraryAttribute] must include a <reference> tag with a 'name' attribute with the same value as the [RequiredLibraryAttribute]. For example [RequiredLibrary("Excel")] mandates <reference name="Excel" />.. + /// + public static string MissingInspectionReferenceTagDescription { + get { + return ResourceManager.GetString("MissingInspectionReferenceTagDescription", resourceCulture); + } + } + + /// + /// Looks up a localized string similar to XML documentation for type '{0}' is missing a '<reference name="{1}">' tag.. + /// + public static string MissingInspectionReferenceTagMessageFormat { + get { + return ResourceManager.GetString("MissingInspectionReferenceTagMessageFormat", resourceCulture); + } + } + + /// + /// Looks up a localized string similar to Missing xml-doc 'summary' tag. + /// + public static string MissingInspectionSummaryTag { + get { + return ResourceManager.GetString("MissingInspectionSummaryTag", resourceCulture); + } + } + + /// + /// Looks up a localized string similar to All inspections must have a short <summary> xml-doc comment describing what the inspection is looking for, that reads comfortably in IntelliSense.. + /// + public static string MissingInspectionSummaryTagDescription { + get { + return ResourceManager.GetString("MissingInspectionSummaryTagDescription", resourceCulture); + } + } + + /// + /// Looks up a localized string similar to XML documentation for type '{0}' is missing a <summary> tag.. + /// + public static string MissingInspectionSummaryTagMessageFormat { + get { + return ResourceManager.GetString("MissingInspectionSummaryTagMessageFormat", resourceCulture); + } + } + + /// + /// Looks up a localized string similar to Missing xml-doc 'why' tag. + /// + public static string MissingInspectionWhyTag { + get { + return ResourceManager.GetString("MissingInspectionWhyTag", resourceCulture); + } + } + + /// + /// Looks up a localized string similar to Inspections xml-doc must have a 'why' tag that contains a paragraph explaining the reasoning behind the inspection.. + /// + public static string MissingInspectionWhyTagDescription { + get { + return ResourceManager.GetString("MissingInspectionWhyTagDescription", resourceCulture); + } + } + + /// + /// Looks up a localized string similar to XML documentation for type '{0}' is missing a <why> tag.. + /// + public static string MissingInspectionWhyTagMessageFormat { + get { + return ResourceManager.GetString("MissingInspectionWhyTagMessageFormat", resourceCulture); + } + } + /// /// Looks up a localized string similar to COM-visible interfaces must have an explicit InterfaceType attribute, typically set to Dual or Dispatch for event interfaces. . /// - internal static string MissingInterfaceTypeDescription { + public static string MissingInterfaceTypeDescription { get { return ResourceManager.GetString("MissingInterfaceTypeDescription", resourceCulture); } @@ -216,7 +324,7 @@ internal class Resources { /// /// Looks up a localized string similar to MissingInterfaceType. /// - internal static string MissingInterfaceTypeId { + public static string MissingInterfaceTypeId { get { return ResourceManager.GetString("MissingInterfaceTypeId", resourceCulture); } @@ -225,7 +333,7 @@ internal class Resources { /// /// Looks up a localized string similar to COM-visible interface '{0}' does not have an explicit InterfaceType attribute with the type of interface set. InterfaceIsDual is the recommended choice, unless it's an event, in which case, InterfaceIsIDispatch is recommended instead.. /// - internal static string MissingInterfaceTypeMessageFormat { + public static string MissingInterfaceTypeMessageFormat { get { return ResourceManager.GetString("MissingInterfaceTypeMessageFormat", resourceCulture); } @@ -234,7 +342,7 @@ internal class Resources { /// /// Looks up a localized string similar to Missing InterfaceType Attribute. /// - internal static string MissingInterfaceTypeTitle { + public static string MissingInterfaceTypeTitle { get { return ResourceManager.GetString("MissingInterfaceTypeTitle", resourceCulture); } @@ -243,7 +351,7 @@ internal class Resources { /// /// Looks up a localized string similar to COM-visible classes must have an explicit ProgId attribute. This is required to avoid verisoning problems. Refer to RubberduckProgId constants.. /// - internal static string MissingProgIdDescription { + public static string MissingProgIdDescription { get { return ResourceManager.GetString("MissingProgIdDescription", resourceCulture); } @@ -252,7 +360,7 @@ internal class Resources { /// /// Looks up a localized string similar to MissingProgId. /// - internal static string MissingProgIdId { + public static string MissingProgIdId { get { return ResourceManager.GetString("MissingProgIdId", resourceCulture); } @@ -261,7 +369,7 @@ internal class Resources { /// /// Looks up a localized string similar to COM-visible class '{0}' does not have an explicit ProgId attribute that references a RubberduckProgId constant.. /// - internal static string MissingProgIdMessageFormat { + public static string MissingProgIdMessageFormat { get { return ResourceManager.GetString("MissingProgIdMessageFormat", resourceCulture); } @@ -270,10 +378,46 @@ internal class Resources { /// /// Looks up a localized string similar to Missing ProgId Attribute. /// - internal static string MissingProgIdTitle { + public static string MissingProgIdTitle { get { return ResourceManager.GetString("MissingProgIdTitle", resourceCulture); } } + + /// + /// Looks up a localized string similar to Missing 'RequiredLibrary' attribute. + /// + public static string MissingRequiredLibAttribute { + get { + return ResourceManager.GetString("MissingRequiredLibAttribute", resourceCulture); + } + } + + /// + /// Looks up a localized string similar to The <reference name="RequiredLibrary" /> tag means to document the presence of a [RequiredLibraryAttribute]. If the attribute is correctly missing, the xml-doc tag should be removed.. + /// + public static string MissingRequiredLibAttributeDescription { + get { + return ResourceManager.GetString("MissingRequiredLibAttributeDescription", resourceCulture); + } + } + + /// + /// Looks up a localized string similar to XML documentation of type '{0}' includes a <reference> tag, but no corresponding [RequiredLibraryAttribute] is decorating the inspection type. Expected: [RequiredLibrary("{1}")].. + /// + public static string MissingRequiredLibAttributeMessageFormat { + get { + return ResourceManager.GetString("MissingRequiredLibAttributeMessageFormat", resourceCulture); + } + } + + /// + /// Looks up a localized string similar to Project website compatibility. + /// + public static string XmlDocAnalyzerCategory { + get { + return ResourceManager.GetString("XmlDocAnalyzerCategory", resourceCulture); + } + } } } diff --git a/RubberduckCodeAnalysis/Resources.resx b/RubberduckCodeAnalysis/Resources.resx index f9b3eadb24..0c7535f9d0 100644 --- a/RubberduckCodeAnalysis/Resources.resx +++ b/RubberduckCodeAnalysis/Resources.resx @@ -153,6 +153,15 @@ Missing ComDefaultInterface Attribute + + Missing xml-doc 'example' tag + + + Inspections xml-doc should have at least one 'example' tag, ideally two. If only one example is provided, website assumes the code example triggers the inspection. If two examples are provided, the second example is assumed to not trigger the inspection. Any further example is assumed to trigger the inspection. + + + XML documentation of type '{0}' has no <example> tag. + COM-visible types must have an explicit Guid attribute. This is required to avoid verisoning problems. Refer to RubberduckGuid constants. An optional longer localizable description of the diagnostic. @@ -168,6 +177,33 @@ Missing Guid Attribute The title of the diagnostic. + + Missing xml-doc 'reference' tag + + + XML documentation for inspections with a [RequiredLibraryAttribute] must include a <reference> tag with a 'name' attribute with the same value as the [RequiredLibraryAttribute]. For example [RequiredLibrary("Excel")] mandates <reference name="Excel" />. + + + XML documentation for type '{0}' is missing a '<reference name="{1}">' tag. + + + Missing xml-doc 'summary' tag + + + All inspections must have a short <summary> xml-doc comment describing what the inspection is looking for, that reads comfortably in IntelliSense. + + + XML documentation for type '{0}' is missing a <summary> tag. + + + Missing xml-doc 'why' tag + + + Inspections xml-doc must have a 'why' tag that contains a paragraph explaining the reasoning behind the inspection. + + + XML documentation for type '{0}' is missing a <why> tag. + COM-visible interfaces must have an explicit InterfaceType attribute, typically set to Dual or Dispatch for event interfaces. @@ -192,4 +228,16 @@ Missing ProgId Attribute + + Missing 'RequiredLibrary' attribute + + + The <reference name="RequiredLibrary" /> tag means to document the presence of a [RequiredLibraryAttribute]. If the attribute is correctly missing, the xml-doc tag should be removed. + + + XML documentation of type '{0}' includes a <reference> tag, but no corresponding [RequiredLibraryAttribute] is decorating the inspection type. Expected: [RequiredLibrary("{1}")]. + + + Project website compatibility + \ No newline at end of file diff --git a/RubberduckCodeAnalysis/RubberduckCodeAnalysis.csproj b/RubberduckCodeAnalysis/RubberduckCodeAnalysis.csproj index 64bedd6e72..d123cd27aa 100644 --- a/RubberduckCodeAnalysis/RubberduckCodeAnalysis.csproj +++ b/RubberduckCodeAnalysis/RubberduckCodeAnalysis.csproj @@ -134,4 +134,17 @@ 4.3.0 + + + True + True + Resources.resx + + + + + PublicResXFileCodeGenerator + Resources.Designer.cs + + \ No newline at end of file diff --git a/RubberduckTests/Inspections/ObsoleteWhileWendInspectionTests.cs b/RubberduckTests/Inspections/ObsoleteWhileWendInspectionTests.cs new file mode 100644 index 0000000000..fd9ded3d5d --- /dev/null +++ b/RubberduckTests/Inspections/ObsoleteWhileWendInspectionTests.cs @@ -0,0 +1,84 @@ +using NUnit.Framework; +using Rubberduck.Parsing.Inspections.Abstract; +using RubberduckTests.Mocks; +using System.Collections.Generic; +using System.Linq; +using System.Threading; +using Rubberduck.CodeAnalysis.Inspections.Concrete; + +namespace RubberduckTests.Inspections +{ + [TestFixture] + public class ObsoleteWhileWendInspectionTests + { + private IEnumerable Inspect(string inputCode) + { + var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _); + using (var state = MockParser.CreateAndParse(vbe.Object)) + { + var inspection = new ObsoleteWhileWendStatementInspection(state); + var inspector = InspectionsHelper.GetInspector(inspection); + return inspector.FindIssuesAsync(state, CancellationToken.None).Result; + } + } + + [Test] + [Category("Inspections")] + public void ObsoleteWhileWendLoop_NoWhileWendLoop_NoResult() + { + const string inputCode = @" +Sub Foo() + Do While True + Loop +End Sub +"; + var results = Inspect(inputCode); + Assert.AreEqual(0, results.Count()); + } + + [Test] + [Category("Inspections")] + public void ObsoleteWhileWendLoop_IgnoredWhileWendLoop_NoResult() + { + const string inputCode = @" +Sub Foo() + '@Ignore ObsoleteWhileWendStatement + While True + Wend +End Sub +"; + var results = Inspect(inputCode); + Assert.AreEqual(0, results.Count()); + } + + [Test] + [Category("Inspections")] + public void ObsoleteWhileWendLoop_EmptyBody_ReturnsResult() + { + const string inputCode = @" +Sub Foo() + While True + Wend +End Sub +"; + var results = Inspect(inputCode); + Assert.AreEqual(1, results.Count()); + } + + [Test] + [Category("Inspections")] + public void ObsoleteWhileWendLoop_NonEmptyBody_ReturnsResult() + { + const string inputCode = @" +Sub Foo() + Dim bar As Long + While bar < 12 + bar = bar + 1 + Wend +End Sub +"; + var results = Inspect(inputCode); + Assert.AreEqual(1, results.Count()); + } + } +} \ No newline at end of file diff --git a/RubberduckTests/QuickFixes/ReplaceObsoleteErrorStatementQuickFixTests.cs b/RubberduckTests/QuickFixes/ReplaceObsoleteErrorStatementQuickFixTests.cs index 5e60805765..c6e7acf058 100644 --- a/RubberduckTests/QuickFixes/ReplaceObsoleteErrorStatementQuickFixTests.cs +++ b/RubberduckTests/QuickFixes/ReplaceObsoleteErrorStatementQuickFixTests.cs @@ -11,15 +11,15 @@ public class ReplaceObsoleteErrorStatementQuickFixTests : QuickFixTestBase { [Test] [Category("QuickFixes")] - public void ObsoleteCommentSyntax_QuickFixWorks() + public void ObsoleteErrorStatement_QuickFixWorks() { - const string inputCode = - @"Sub Foo() + const string inputCode = @" +Sub Foo() Error 91 End Sub"; - const string expectedCode = - @"Sub Foo() + const string expectedCode = @" +Sub Foo() Err.Raise 91 End Sub"; @@ -28,18 +28,18 @@ Err.Raise 91 } [Test] [Category("QuickFixes")] - public void ObsoleteCommentSyntax_QuickFixWorks_ProcNamedError() + public void ObsoleteErrorStatement_QuickFixWorks_ProcNamedError() { - const string inputCode = - @"Sub Error(val as Integer) + const string inputCode = @" +Sub Error(val as Integer) End Sub Sub Foo() Error 91 End Sub"; - const string expectedCode = - @"Sub Error(val as Integer) + const string expectedCode = @" +Sub Error(val as Integer) End Sub Sub Foo() @@ -52,16 +52,16 @@ Err.Raise 91 [Test] [Category("QuickFixes")] - public void ObsoleteCommentSyntax_QuickFixWorks_UpdateCommentHasContinuation() + public void ObsoleteErrorStatement_QuickFixWorks_UpdateCommentHasContinuation() { - const string inputCode = - @"Sub Foo() + const string inputCode = @" +Sub Foo() Error _ 91 End Sub"; - const string expectedCode = - @"Sub Foo() + const string expectedCode = @" +Sub Foo() Err.Raise _ 91 End Sub"; @@ -73,15 +73,15 @@ Err.Raise _ [Test] [Category("QuickFixes")] - public void ObsoleteCommentSyntax_QuickFixWorks_UpdateComment_LineHasCode() + public void ObsoleteErrorStatement_QuickFixWorks_UpdateComment_LineHasCode() { - const string inputCode = - @"Sub Foo() + const string inputCode = @" +Sub Foo() Dim foo: Error 91 End Sub"; - const string expectedCode = - @"Sub Foo() + const string expectedCode = @" +Sub Foo() Dim foo: Err.Raise 91 End Sub"; diff --git a/RubberduckTests/QuickFixes/ReplaceWhileWendWithDoWhileLoopQuickFixTests.cs b/RubberduckTests/QuickFixes/ReplaceWhileWendWithDoWhileLoopQuickFixTests.cs new file mode 100644 index 0000000000..fc298e5a05 --- /dev/null +++ b/RubberduckTests/QuickFixes/ReplaceWhileWendWithDoWhileLoopQuickFixTests.cs @@ -0,0 +1,53 @@ +using NUnit.Framework; +using Rubberduck.CodeAnalysis.Inspections.Concrete; +using Rubberduck.CodeAnalysis.QuickFixes; +using Rubberduck.Parsing.Inspections.Abstract; +using Rubberduck.Parsing.VBA; + +namespace RubberduckTests.QuickFixes +{ + [TestFixture] + public class ReplaceWhileWendWithDoWhileLoopQuickFixTests : QuickFixTestBase + { + protected override IQuickFix QuickFix(RubberduckParserState state) + => new ReplaceWhileWendWithDoWhileLoopQuickFix(); + + [Test] + [Category("QuickFixes")] + public void ObsoleteWhileWendStatement_QuickFixWorks() + { + const string input = @" +Sub Foo() + While True + Wend +End Sub +"; + const string expected = @" +Sub Foo() + Do While True + Loop +End Sub +"; + var actual = ApplyQuickFixToFirstInspectionResult(input, state => new ObsoleteWhileWendStatementInspection(state)); + Assert.AreEqual(expected, actual); + } + + [Test] + [Category("QuickFixes")] + public void ObsoleteWhileWendStatement_InstructionsSeparator_QuickFixWorks() + { + const string input = @" +Sub Foo() + While True : DoSomething : Wend +End Sub +"; + const string expected = @" +Sub Foo() + Do While True : DoSomething : Loop +End Sub +"; + var actual = ApplyQuickFixToFirstInspectionResult(input, state => new ObsoleteWhileWendStatementInspection(state)); + Assert.AreEqual(expected, actual); + } + } +} \ No newline at end of file diff --git a/appveyor.yml b/appveyor.yml index 56f7a5d926..abc606d3d5 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -108,6 +108,8 @@ after_test: artifacts: - path: Rubberduck.Deployment\InnoSetup\Installers\Rubberduck.Setup.*.exe name: Rubberduck + - path: Rubberduck.Deployment\bin\Rubberduck.CodeAnalysis.xml + name: InspectionDocs deploy: - provider: GitHub tag: RETAGMEWITHAMESSAGE @@ -117,7 +119,7 @@ deploy: description: "Built with :heart: by AppVeyor CI on [$(appveyor_repo_branch)] - https://ci.appveyor.com/project/rubberduck-vba/rubberduck/build/$(appveyor_build_version)" auth_token: secure: NVAZgFRSk566SP5QDge5gYRWCaLi4NJJPTNk3QengH15wL9iVldfrFOllbzKXExq - artifact: Rubberduck + artifact: Rubberduck, InspectionDocs on: branch: master - provider: GitHub @@ -128,7 +130,7 @@ deploy: description: "AppVeyor build on [$(appveyor_repo_branch)] - https://ci.appveyor.com/project/rubberduck-vba/rubberduck/build/$(appveyor_build_version)" auth_token: secure: NVAZgFRSk566SP5QDge5gYRWCaLi4NJJPTNk3QengH15wL9iVldfrFOllbzKXExq - artifact: Rubberduck + artifact: Rubberduck, InspectionDocs on: branch: next diff --git a/docs/Rubberduck.CodeAnalysis.xml b/docs/Rubberduck.CodeAnalysis.xml new file mode 100644 index 0000000000..ce103a5ff3 --- /dev/null +++ b/docs/Rubberduck.CodeAnalysis.xml @@ -0,0 +1,2330 @@ + + + + Rubberduck.CodeAnalysis + + + + + The name of the metric. Used for localization purposes as well as a uniquely identifying name to disambiguate between metrics. + + + + + The aggregation level that this metric applies to. + + + + + A CodeMetricsResult. Each result is attached to a Declaration. + Usually this declaration would be a Procedure (Function/Sub/Property). + Some metrics are only useful on Module level, some even on Project level. + + Some metrics may be aggregated to obtain a metric for a "higher hierarchy level" + + + + + The declaration that this result refers to. + + + + + The Metric kind that this result belongs to. Only results belonging to the **same** metric can be aggregated. + + + + + A string representation of the value. + + + + + Flags 'While...Wend' loops as obsolete. + + + 'While...Wend' loops were made obsolete when 'Do While...Loop' statements were introduced. + 'While...Wend' loops cannot be exited early without a GoTo jump; 'Do...Loop' statements can be conditionally exited with 'Exit Do'. + + + + + + + + + + + Default constructor required for XML serialization. + + + + + Gets a localized string representing a short name/description for the inspection. + + + + + Gets the type of inspection; used for regrouping inspections. + + + + + The inspection type name, obtained by reflection. + + + + + Inspection severity level. Can control whether an inspection is enabled. + + + + + Meta-information about why an inspection exists. + + + + + Gets a localized string representing the type of inspection. + + + + + + Gets a string representing the text that must be present in an + @Ignore annotation to disable the inspection at a given site. + + + + + Gets all declarations in the parser state without an @Ignore annotation for this inspection. + + + + + Gets all user declarations in the parser state without an @Ignore annotation for this inspection. + + + + + A method that inspects the parser state and returns all issues it can find. + + + + + + + Gets the information needed to select the target instruction in the VBE. + + + + + WARNING: This property can have side effects. It can change the ActiveVBProject if the result has a null Declaration, + which causes a flicker in the VBE. This should only be called if it is *absolutely* necessary. + + + + + Locates public User-Defined Function procedures accidentally named after a cell reference. + + + + Another good reason to avoid numeric suffixes: if the function is meant to be used as a UDF in a cell formula, + the worksheet cell by the same name takes precedence and gets the reference, and the function is never invoked. + + + + + + + + + + + Identifies uses of 'IsMissing' involving a non-parameter argument. + + + 'IsMissing' only returns True when an optional Variant parameter was not supplied as an argument. + This inspection flags uses that attempt to use 'IsMissing' for other purposes, resulting in conditions that are always False. + + + + + + + + + + + Warns about 'Declare' statements that are using the obsolete/unsupported 'CDecl' calling convention on Windows. + + + The CDecl calling convention is only implemented in VBA for Mac; if Rubberduck can see it (Rubberduck only runs on Windows), + then the declaration is using an unsupported (no-op) calling convention on Windows. + + + + + + + + + + + Flags usages of members marked as obsolete with an @Obsolete("justification") Rubberduck annotation. + + + Marking members as obsolete can help refactoring a legacy code base. This inspection is a tool that makes it easy to locate obsolete member calls. + + + + + + + + + + + A ThunderCode inspection that locates instances of various keywords and reserved identifiers used as Type or Enum member names. + + + This inpection is flagging code we dubbed "ThunderCode", + code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + While perfectly legal as Type or Enum member names, these identifiers should be avoided: + they need to be square-bracketed everywhere they are used. + + + + + A ThunderCode inspection that locates certain specific instances of line continuations in places we'd never think to put them. + + + This inpection is flagging code we dubbed "ThunderCode", + code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + While perfectly legal, these line continuations serve no purpose and should be removed. + + + Note that the inspection only checks a subset of possible "evil" line continatuions + for both simplicity and performance reasons. Exhaustive inspection would likely take too much effort. + + + + + A ThunderCode inspection that locates negative line numbers. + + + This inpection is flagging code we dubbed "ThunderCode", + code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + The VBE does allow rather strange and unbelievable things to happen. + + + + + A ThunderCode inspection that locates non-breaking spaces hidden in identifier names. + + + This inpection is flagging code we dubbed "ThunderCode", + code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + This inspection may accidentally reveal non-breaking spaces in code copied and pasted from a website. + + + + + A ThunderCode inspection that locates instances of 'On Error GoTo -1' statements. + + + This inpection is flagging code we dubbed "ThunderCode", + code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver. + 'On Error GoTo -1' is poorly documented and uselessly complicates error handling. + + + + + Warns about parameters passed by value being assigned a new value in the body of a procedure. + + + Debugging is easier if the procedure's initial state is preserved and accessible anywhere within its scope. + Mutating the inputs destroys the initial state, and makes the intent ambiguous: if the calling code is meant + to be able to access the modified values, then the parameter should be passed ByRef; the ByVal modifier might be a bug. + + + + + + + + + + + Warns about a variable that is assigned, and then re-assigned before the first assignment is read. + + + The first assignment is likely redundant, since it is being overwritten by the second. + + + + + + + + + + + Indicates that the value of a hidden VB attribute is out of sync with the corresponding Rubberduck annotation comment. + + + Keeping Rubberduck annotation comments in sync with the hidden VB attribute values, surfaces these hidden attributes in the VBE code panes; + Rubberduck can rewrite the attributes to match the corresponding annotation comment. + + + + + + + + + + + Identifies redundant Boolean expressions in conditionals. + + + A Boolean expression never needs to be compared to a Boolean literal in a conditional expression. + + + + + + + + + + + Locates 'Const' declarations that are never referenced. + + + Declarations that are never used should be removed. + + + + + + + + + + + This inspection means to indicate when the project has not been renamed. + + + VBA projects should be meaningfully named, to avoid namespace clashes when referencing other VBA projects. + + + + + Warns about Def[Type] statements. + + + These declarative statements make the first letter of identifiers determine the data type. + + + + + + + + Warns about duplicated annotations. + + + Rubberduck annotations should not be specified more than once for a given module, member, variable, or expression. + + + + + + + + + + + Identifies empty 'Case' blocks that can be safely removed. + + + Case blocks in VBA do not "fall through"; an empty 'Case' block might be hiding a bug. + + + 0 + Debug.Print foo ' does not run if foo is 0. + End Select + End Sub + ]]> + + + 0 + '...code... + End Select + End Sub + ]]> + + + + + Identifies empty 'Do...Loop While' blocks that can be safely removed. + + + Dead code should be removed. A loop without a body is usually redundant. + + + + + + + + + + + Identifies empty 'Else' blocks that can be safely removed. + + + Empty code blocks are redundant, dead code that should be removed. They can also be misleading about their intent: + an empty block may be signalling an unfinished thought or an oversight. + + + + + + + + + + + Identifies empty 'For Each...Next' blocks that can be safely removed. + + + Dead code should be removed. A loop without a body is usually redundant. + + + + + + + + + + + Identifies empty 'For...Next' blocks that can be safely removed. + + + Dead code should be removed. A loop without a body is usually redundant. + + + + + + + + + + + Identifies empty 'If' blocks. + + + Conditional expression is inverted; there would not be a need for an 'Else' block otherwise. + + + + + + + + + + + Flags empty code modules. + + + An empty module does not need to exist and can be safely removed. + + + + + Flags uses of an empty string literal (""). + + + Standard library constant 'vbNullString' is more explicit about its intent, and should be preferred to a string literal. + While the memory gain is meaningless, an empty string literal still takes up 2 bytes of memory, + but 'vbNullString' is a null string pointer, and doesn't. + + + + + + + + + + + Identifies empty 'While...Wend' blocks that can be safely removed. + + + Dead code should be removed. A loop without a body is usually redundant. + + + + + + + + + + + Flags publicly exposed instance fields. + + + Instance fields are the implementation details of a object's internal state; exposing them directly breaks encapsulation. + Often, an object only needs to expose a 'Get' procedure to expose an internal instance field. + + + + + + + + + + + Warns about late-bound WorksheetFunction calls made against the extended interface of the Application object. + + + + An early-bound, equivalent function likely exists in the object returned by the Application.WorksheetFunction property; + late-bound member calls will fail at run-time with error 438 if there is a typo (a typo fails to compile for an early-bound member call). + Late-bound worksheet functions will return a Variant/Error given invalid inputs; + the equivalent early-bound member calls raise a more VB-idiomatic runtime error given the same invalid inputs. + A Variant/Error value cannot be coerced into any other data type, be it for assignment or comparison. + Trying to compare or assign a Variant/Error to another data type will throw error 13 "type mismatch" at run-time. + Consider using the early-bound equivalent function instead. + + + 15 Then + ' won't run, error 13 "type mismatch" will be thrown when Variant/Error is compared to an Integer. + End If + End Sub + ]]> + + + 15 Then ' throws error 1004 + ' won't run, error 1004 is thrown when "ABC" is processed by WorksheetFunction.Sum, before it returns. + End If + End Sub + ]]> + + + + Locates instances of member calls made against the result of a Range.Find/FindNext/FindPrevious method, without prior validation. + + + Range.Find methods return a Range object reference that refers to the cell containing the search string; + this object reference will be Nothing if the search didn't turn up any results, and a member call against Nothing will raise run-time error 91. + + + + + + + + + + + Locates unqualified Worksheet.Range/Cells/Columns/Rows member calls that implicitly refer to ActiveSheet. + + + + Implicit references to the active worksheet rarely mean to be working with *whatever worksheet is currently active*. + By explicitly qualifying these member calls with a specific Worksheet object, the assumptions are removed, the code + is more robust, and will be less likely to throw run-time error 1004 or produce unexpected results + when the active sheet isn't the expected one. + + + + + + + + + + + Locates unqualified Workbook.Worksheets/Sheets/Names member calls that implicitly refer to ActiveWorkbook. + + + + Implicit references to the active workbook rarely mean to be working with *whatever workbook is currently active*. + By explicitly qualifying these member calls with a specific Workbook object, the assumptions are removed, the code + is more robust, and will be less likely to throw run-time error 1004 or produce unexpected results + when the active workbook isn't the expected one. + + + + + + + + + + + Locates ThisWorkbook.Worksheets and ThisWorkbook.Sheets calls that appear to be dereferencing a worksheet that is already accessible at compile-time with a global-scope identifier. + + + Sheet names can be changed by the user, as can a worksheet's index in ThisWorkbook.Worksheets. + Worksheets that exist in ThisWorkbook at compile-time are more reliably programmatically accessed using their CodeName, + which cannot be altered by the user without accessing the VBE and altering the VBA project. + + + + Inspection only evaluates hard-coded string literals; string-valued expressions evaluating into a sheet name are ignored. + + + + + + + + + + + Warns when a user function's return value is never used, at any of its call sites. + + + A 'Function' procedure normally means its return value to be captured and consumed by the calling code. + It's possible that not all call sites need the return value, but if the value is systematically discarded then this + means the function is side-effecting, and thus should probably be a 'Sub' procedure instead. + + + + + + + + + + + Warns about host-evaluated square-bracketed expressions. + + + Host-evaluated expressions should be implementable using the host application's object model. + If the expression yields an object, member calls against that object are late-bound. + + + + + + + + + + + Flags identifiers that use [Systems] Hungarian Notation prefixes. + + + Systems Hungarian (encoding data types in variable names) stemmed from a misunderstanding of what its inventor meant + when they described that prefixes identified the "kind" of variable in a naming scheme dubbed Apps Hungarian. + Modern naming conventions in all programming languages heavily discourage the use of Systems Hungarian prefixes. + + + + + + + + + + + Flags invalid Rubberduck annotation comments. + + + Rubberduck is correctly parsing an annotation, but that annotation is illegal in that context. + + + + + + + + + + + + Identifies implicit default member calls. + + + Code should do what it says, and say what it does. Implicit default member calls generally do the opposite of that. + + + + + + + + + + + Highlights implicit Public access modifiers in user code. + + + In modern VB (VB.NET), the implicit access modifier is Private, as it is in most other programming languages. + Making the Public modifiers explicit can help surface potentially unexpected language defaults. + + + + + + + + + + + Warns about 'Function' and 'Property Get' procedures that don't have an explicit return type. + + + All functions return something, whether a type is specified or not. The implicit default is 'Variant'. + + + + + + + + + + + Identifies obsolete 16-bit integer variables. + + + Modern processors are optimized for processing 32-bit integers; internally, a 16-bit integer is still stored as a 32-bit value. + Unless code is interacting with APIs that require a 16-bit integer, a Long (32-bit integer) should be used instead. + + + + + + + + + + + Identifies uses of 'IsMissing' involving non-variant, non-optional, or array parameters. + + + 'IsMissing' only returns True when an optional Variant parameter was not supplied as an argument. + This inspection flags uses that attempt to use 'IsMissing' for other purposes, resulting in conditions that are always False. + + + + + + + + + + + Identifies line labels that are never referenced, and therefore superfluous. + + + Line labels are useful for GoTo, GoSub, Resume, and On Error statements; but the intent of a line label + can be confusing if it isn't referenced by any such instruction. + + + + + + + + + + + Warns about member calls against an extensible interface, that cannot be validated at compile-time. + + + Extensible COM types can have members attached at run-time; VBA cannot bind these member calls at compile-time. + If there is an early-bound alternative way to achieve the same result, it should be preferred. + + + + + + + + + + + Warns about a malformed Rubberduck annotation that is missing an argument. + + + Some annotations require arguments; if the argument isn't specified, the annotation is nothing more than an obscure comment. + + + + + + + + + + + Indicates that a Rubberduck annotation is documenting the presence of a VB attribute that is actually missing. + + + Rubberduck annotations mean to document the presence of hidden VB attributes; this inspection flags annotations that + do not have a corresponding VB attribute. + + + + + + + + + + + Indicates that a hidden VB attribute is present for a member, but no Rubberduck annotation is documenting it. + + + Rubberduck annotations mean to document the presence of hidden VB attributes; this inspection flags members that + do not have a Rubberduck annotation corresponding to the hidden VB attribute. + + + + + + + + + + + Indicates that a hidden VB attribute is present for a module, but no Rubberduck annotation is documenting it. + + + Rubberduck annotations mean to document the presence of hidden VB attributes; this inspection flags modules that + do not have a Rubberduck annotation corresponding to the hidden VB attribute. + + + + + + + + + + + Warns about module-level declarations made using the 'Dim' keyword. + + + Private module variables should be declared using the 'Private' keyword. While 'Dim' is also legal, it should preferably be + restricted to declarations of procedure-scoped local variables, for consistency, since public module variables are declared with the 'Public' keyword. + + + + + + + + + + + Indicates that a user module is missing a @Folder Rubberduck annotation. + + + Modules without a custom @Folder annotation will be grouped under the default folder in the Code Explorer toolwindow. + By specifying a custom @Folder annotation, modules can be organized by functionality rather than simply listed. + + + + + + + + + + + Locates module-level fields that can be moved to a smaller scope. + + + Module-level variables that are only used in a single procedure can often be declared in that procedure's scope. + Declaring variables closer to where they are used generally makes the code easier to follow. + + + + + + + + + + + Flags parameters declared across multiple physical lines of code. + + + When splitting a long list of parameters across multiple lines, care should be taken to avoid splitting a parameter declaration in two. + + + + + + + + + + + Flags declaration statements spanning multiple physical lines of code. + + + Declaration statements should generally declare a single variable. + + + + + + + + + + + Warns about 'Function' and 'Property Get' procedures whose return value is not assigned. + + + Both 'Function' and 'Property Get' accessors should always return something. Omitting the return assignment is likely a bug. + + + + + + + + + + + A visitor that visits a member's body and returns true if any LET statement (assignment) is assigning the specified name. + + + + + Warns about assignments that appear to be assigning an object reference without the 'Set' keyword. + + + Omitting the 'Set' keyword will Let-coerce the right-hand side (RHS) of the assignment expression. If the RHS is an object variable, + then the assignment is implicitly assigning to that object's default member, which may raise run-time error 91 at run-time. + + + + + + + + + + + Locates explicit 'Call' statements. + + + The 'Call' keyword is obsolete and redundant, since call statements are legal and generally more consistent without it. + + + + + + + + + + + Locates legacy 'Rem' comments. + + + Modern VB comments use a single quote character (') to denote the beginning of a comment: the legacy 'Rem' syntax is obsolete. + + + + + + + + + + + Locates legacy 'Error' statements. + + + The legacy syntax is obsolete; prefer 'Err.Raise' instead. + + + + + + + + + + + Locates legacy 'Global' declaration statements. + + + The legacy syntax is obsolete; use the 'Public' keyword instead. + + + + + + + + + + + Locates explicit 'Let' assignments. + + + The legacy syntax is obsolete/redundant; prefer implicit Let-coercion instead. + + + + + + + + + + + Flags declarations where a type hint is used in place of an 'As' clause. + + + Type hints were made obsolete when declaration syntax introduced the 'As' keyword. Prefer explicit type names over type hint symbols. + + + + + + + + + + + Flags obsolete 'On Local Error' statements. + + + All errors are "local" - the keyword is redundant/confusing and should be removed. + + + + + + + + + + + Flags modules that specify Option Base 1. + + + Implicit array lower bound is 0 by default, and Option Base 1 makes it 1. While compelling in a 1-based environment like the Excel object model, + having an implicit lower bound of 1 for implicitly-sized user arrays does not change the fact that arrays are always better off with explicit boundaries. + Because 0 is always the lower array bound in many other programming languages, this option may trip a reader/maintainer with a different background. + + + + + + + + + + + Flags modules that omit Option Explicit. + + + This option makes variable declarations mandatory. Without it, a typo gets compiled as a new on-the-spot Variant/Empty variable with a new name. + Omitting this option amounts to refusing the little help the VBE can provide with compile-time validation. + + + + + + + + + + + Flags parameters that are passed by reference (ByRef), but could be passed by value (ByVal). + + + Explicitly specifying a ByVal modifier on a parameter makes the intent explicit: this parameter is not meant to be assigned. In contrast, + a parameter that is passed by reference (implicitly, or explicitly ByRef) makes it ambiguous from the calling code's standpoint, whether the + procedure might re-assign these ByRef values and introduce a bug. + + + + + + + + + + + Identifies parameter declarations that are not used. + + + Declarations that are not used anywhere should probably be removed. + + + Not all unused parameters can/should be removed: ignore any inspection results for + event handler procedures and interface members that Rubberduck isn't recognizing as such. + + + + + + + + + + + Warns about 'Sub' procedures that could be refactored into a 'Function'. + + + Idiomatic VB code uses 'Function' procedures to return a single value. If the procedure isn't side-effecting, consider writing is as a + 'Function' rather than a 'Sub' the returns a result through a 'ByRef' parameter. + + + + + + + + + + + Locates procedures that are never invoked from user code. + + + Unused procedures are dead code that should probably be removed. Note, a procedure may be effectively "not used" in code, but attached to some + Shape object in the host document: in such cases the inspection result should be ignored. An event handler procedure that isn't being + resolved as such, may also wrongly trigger this inspection. + + + Not all unused procedures can/should be removed: ignore any inspection results for + event handler procedures and interface members that Rubberduck isn't recognizing as such. + + + + + + + + + + + We cannot determine whether exposed members of standard modules are called or not, + so we assume they are instead of flagging them as "never called". + + + + + Identifies redundant ByRef modifiers. + + + Out of convention or preference, explicit ByRef modifiers could be considered redundant since they are the implicit default. + This inspection can ensure the consistency of the convention. + + + + + + + + + + + Identifies redundant module options that are set to their implicit default. + + + Module options that are redundant can be safely removed. Disable this inspection if your convention is to explicitly specify them; a future + inspection may be used to enforce consistently explicit module options. + + + + + + + + + + + Identifies auto-assigned object declarations. + + + Auto-assigned objects are automatically re-created as soon as they are referenced. It is therefore impossible to set one such reference + to 'Nothing' and then verifying whether the object 'Is Nothing': it will never be. This behavior is potentially confusing and bug-prone. + + + + + + + + + + + Identifies identifiers that hide/"shadow" other identifiers otherwise accessible in that scope. + + + Global namespace contains a number of perfectly legal identifier names that user code can use. But using these names in user code + effectively "hides" the global ones. In general, avoid shadowing global-scope identifiers if possible. + + + + + + + + + + + Locates 'For' loops where the 'Step' token is omitted. + + + Out of convention or preference, explicit 'Step' specifiers could be considered mandatory; + this inspection can ensure the consistency of the convention. + + + + + + + + + + + Locates 'For' loops where the 'Step' token is specified with the default increment value (1). + + + Out of convention or preference, explicit 'Step 1' specifiers could be considered redundant; + this inspection can ensure the consistency of the convention. + + + + + + + + + + + Locates 'Stop' instructions in user code. + + + While a great debugging tool, 'Stop' instructions should not be reachable in production code; this inspection makes it easy to locate them all. + + + + + + + + + + + Warns when a variable is referenced prior to being assigned. + + + An uninitialized variable is being read, but since it's never assigned, the only value ever read would be the data type's default initial value. + Reading a variable that was never written to in any code path (especially if Option Explicit isn't specified), is likely to be a bug. + + + This inspection may produce false positives when the variable is an array, or if it's passed by reference (ByRef) to a procedure that assigns it. + + + + + + + + + + + Warns about implicit local variables that are used but never declared. + + + If this code compiles, then Option Explicit is omitted and compile-time validation is easily forfeited, even accidentally (e.g. typos). + + + + + + + + + + + Warns about public class members with an underscore in their names. + + + The public interface of any class module can be implemented by any other class module; if the public interface + contains names with underscores, other classes cannot implement it - the code will not compile. Avoid underscores; prefer PascalCase names. + + + + + + + + + + + Finds instances of 'On Error Resume Next' that don't have a corresponding 'On Error GoTo 0' to restore error handling. + + + 'On Error Resume Next' should be constrained to a limited number of instructions, otherwise it supresses error handling + for the rest of the procedure; 'On Error GoTo 0' reinstates error handling. + This inspection helps treating 'Resume Next' and 'GoTo 0' as a code block (similar to 'With...End With'), essentially. + + + + + + + + + + + Flags 'Case' blocks that are semantically unreachable. + + + Unreachable code is certainly unintended, and is probably either redundant, or a bug. + + + Not all unreachable 'Case' blocks may be flagged, depending on expression complexity. + + + + + + + + Flags uses of a number of specific string-centric but Variant-returning functions in various standard library modules. + + + Several functions in the standard library take a Variant parameter and return a Variant result, but an equivalent + string-returning function taking a string parameter exists and should probably be preferred. + + + + + + + + + + + Warns about identifiers that have names that are likely to be too short, disemvoweled, or appended with a numeric suffix. + + + Meaningful, pronounceable, unabbreviated names read better and leave less room for interpretation. + Moreover, names suffixed with a number can indicate the need to look into an array, collection, or dictionary data structure. + + + + + + + + + + + Warns about variables that are never assigned. + + + A variable that is never assigned is probably a sign of a bug. + This inspection may yield false positives if the variable is assigned through a ByRef parameter assignment, or + if UserForm controls fail to resolve, references to these controls in code-behind can be flagged as unassigned and undeclared variables. + + + + + + + + + + + Warns about variables that are never referenced. + + + A variable can be declared and even assigned, but if its value is never referenced, it's effectively an unused variable. + + + + + + + + + + + Warns about variables declared without an explicit data type. + + + A variable declared without an explicit data type is implicitly a Variant/Empty until it is assigned. + + + + + + + + + + + Warns about properties that don't expose a 'Property Get' accessor. + + + Write-only properties are suspicious: if the client code is able to set a property, it should be allowed to read that property as well. + Class design guidelines and best practices generally recommend against write-only properties. + + + + + + + + + + + Determines whether the 'Set' keyword is required (whether it's present or not) for the specified identifier reference. + + The identifier reference to analyze + The parser state + + + + A code inspection quickfix that removes an unused identifier declaration. + + + +