diff --git a/Rubberduck.CodeAnalysis/CodeAnalysisUI.Designer.cs b/Rubberduck.CodeAnalysis/CodeAnalysisUI.Designer.cs
index 8d9c5740a6..18acea2c26 100644
--- a/Rubberduck.CodeAnalysis/CodeAnalysisUI.Designer.cs
+++ b/Rubberduck.CodeAnalysis/CodeAnalysisUI.Designer.cs
@@ -161,6 +161,15 @@ public static string CodeInspectionSettingsPage_Misc {
}
}
+ ///
+ /// Looks up a localized string similar to Ignore Hungarian Notation for UserForm controls.
+ ///
+ public static string CodeInspectionSettingsPage_Misc_IgnoreFormControlHungarianNotation {
+ get {
+ return ResourceManager.GetString("CodeInspectionSettingsPage_Misc_IgnoreFormControlHungarianNotation", resourceCulture);
+ }
+ }
+
///
/// Looks up a localized string similar to Run inspections automatically on successful parse.
///
@@ -493,5 +502,14 @@ public static string GroupingGrid_Filter {
return ResourceManager.GetString("GroupingGrid_Filter", resourceCulture);
}
}
+
+ ///
+ /// Looks up a localized string similar to Parameter array '{0}' is zero-based..
+ ///
+ public static string InconsistentArrayBaseInspection_ParamArray {
+ get {
+ return ResourceManager.GetString("InconsistentArrayBaseInspection_ParamArray", resourceCulture);
+ }
+ }
}
}
diff --git a/Rubberduck.CodeAnalysis/CodeAnalysisUI.fr.resx b/Rubberduck.CodeAnalysis/CodeAnalysisUI.fr.resx
index d647d3adef..adcac16634 100644
--- a/Rubberduck.CodeAnalysis/CodeAnalysisUI.fr.resx
+++ b/Rubberduck.CodeAnalysis/CodeAnalysisUI.fr.resx
@@ -263,4 +263,10 @@
Sévérité:
+
+ Ignorer la notation hongroise pour les contrôles des UserForm
+
+
+ Le tableau de paramètres (ParamArray) '{0}' a zéro pour base.
+
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/CodeAnalysisUI.resx b/Rubberduck.CodeAnalysis/CodeAnalysisUI.resx
index 33bba664e2..3d5bc16189 100644
--- a/Rubberduck.CodeAnalysis/CodeAnalysisUI.resx
+++ b/Rubberduck.CodeAnalysis/CodeAnalysisUI.resx
@@ -1,76 +1,96 @@
+ mimetype: application/x-microsoft.net.object.bytearray.base64
+ value : The object must be serialized into a byte array
+ : using a System.ComponentModel.TypeConverter
+ : and then encoded with base64 encoding.
+ -->
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
-
+
+
@@ -89,13 +109,13 @@
text/microsoft-resx
- 1.3
+ 2.0
- System.Resources.ResXResourceReader, System.Windows.Forms, Version=2.0.3500.0, Culture=neutral, PublicKeyToken=b77a5c561934e089
+ System.Resources.ResXResourceReader, System.Windows.Forms, Version=4.0.0.0, Culture=neutral, PublicKeyToken=b77a5c561934e089
- System.Resources.ResXResourceWriter, System.Windows.Forms, Version=2.0.3500.0, Culture=neutral, PublicKeyToken=b77a5c561934e089
+ System.Resources.ResXResourceWriter, System.Windows.Forms, Version=4.0.0.0, Culture=neutral, PublicKeyToken=b77a5c561934e089Type
@@ -245,4 +265,10 @@
Severity:
+
+ Ignore Hungarian Notation for UserForm controls
+
+
+ Parameter array '{0}' is zero-based.
+
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Abstract/InvalidAnnotationInspectionBase.cs b/Rubberduck.CodeAnalysis/Inspections/Abstract/InvalidAnnotationInspectionBase.cs
new file mode 100644
index 0000000000..d04eec59f0
--- /dev/null
+++ b/Rubberduck.CodeAnalysis/Inspections/Abstract/InvalidAnnotationInspectionBase.cs
@@ -0,0 +1,63 @@
+using Rubberduck.CodeAnalysis.Inspections.Results;
+using Rubberduck.Parsing;
+using Rubberduck.Parsing.Annotations;
+using Rubberduck.Parsing.Symbols;
+using Rubberduck.Parsing.VBA;
+using Rubberduck.Parsing.VBA.DeclarationCaching;
+using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Linq;
+
+namespace Rubberduck.CodeAnalysis.Inspections.Abstract
+{
+ ///
+ /// An inspection that flags invalid annotation comments.
+ ///
+ internal abstract class InvalidAnnotationInspectionBase : InspectionBase
+ {
+ protected InvalidAnnotationInspectionBase(IDeclarationFinderProvider declarationFinderProvider)
+ : base(declarationFinderProvider) { }
+
+ protected QualifiedContext Context(IParseTreeAnnotation pta) =>
+ new QualifiedContext(pta.QualifiedSelection.QualifiedName, pta.Context);
+
+ protected sealed override IEnumerable DoGetInspectionResults(DeclarationFinder finder)
+ {
+ return finder.UserDeclarations(DeclarationType.Module)
+.Where(module => module != null)
+.SelectMany(module => DoGetInspectionResults(module.QualifiedModuleName, finder));
+ }
+
+ protected IInspectionResult InspectionResult(IParseTreeAnnotation pta) =>
+ new QualifiedContextInspectionResult(this, ResultDescription(pta), Context(pta));
+
+ ///
+ /// Gets all invalid annotations covered by this inspection.
+ ///
+ /// All user code annotations.
+ /// All user declarations.
+ /// All identifier references in user code.
+ ///
+ protected abstract IEnumerable GetInvalidAnnotations(
+ IEnumerable annotations,
+ IEnumerable userDeclarations,
+ IEnumerable identifierReferences);
+
+ ///
+ /// Gets an annotation-specific description for an inspection result.
+ ///
+ /// The invalid annotation.
+ ///
+ protected abstract string ResultDescription(IParseTreeAnnotation pta);
+
+ protected sealed override IEnumerable DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
+ {
+ var annotations = finder.FindAnnotations(module);
+ var userDeclarations = finder.Members(module).ToList();
+ var identifierReferences = finder.IdentifierReferences(module).ToList();
+
+ var invalidAnnotations = GetInvalidAnnotations(annotations, userDeclarations, identifierReferences);
+ return invalidAnnotations.Select(InspectionResult).ToList();
+ }
+ }
+}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/AnnotationInIncompatibleComponentTypeInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/AnnotationInIncompatibleComponentTypeInspection.cs
new file mode 100644
index 0000000000..9e38d568a4
--- /dev/null
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/AnnotationInIncompatibleComponentTypeInspection.cs
@@ -0,0 +1,80 @@
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.Parsing;
+using Rubberduck.Parsing.Annotations;
+using Rubberduck.Parsing.Symbols;
+using Rubberduck.Parsing.VBA;
+using Rubberduck.Resources.Inspections;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
+
+namespace Rubberduck.CodeAnalysis.Inspections.Concrete
+{
+ ///
+ /// Flags Rubberduck annotations used in a component type that is incompatible with that annotation.
+ ///
+ ///
+ /// Some annotations can only be used in a specific type of module; others cannot be used in certain types of modules.
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ internal sealed class AnnotationInIncompatibleComponentTypeInspection : InvalidAnnotationInspectionBase
+ {
+ public AnnotationInIncompatibleComponentTypeInspection(IDeclarationFinderProvider declarationFinderProvider)
+ : base(declarationFinderProvider) { }
+
+ protected override IEnumerable GetInvalidAnnotations(
+ IEnumerable annotations,
+ IEnumerable userDeclarations,
+ IEnumerable identifierReferences)
+ {
+ foreach (var pta in annotations)
+ {
+ var annotation = pta.Annotation;
+ var componentType = pta.QualifiedSelection.QualifiedName.ComponentType;
+ if (annotation.RequiredComponentType.HasValue && annotation.RequiredComponentType != componentType
+ || annotation.IncompatibleComponentTypes.Contains(componentType))
+ {
+ yield return pta;
+ }
+ }
+
+ yield break;
+ }
+
+ protected override string ResultDescription(IParseTreeAnnotation pta)
+ {
+ if (pta.Annotation.RequiredComponentType.HasValue)
+ {
+ return string.Format(InspectionResults.ResourceManager.GetString($"{nameof(InvalidAnnotationInspection)}_NotInRequiredComponentType", CultureInfo.CurrentUICulture),
+ pta.Annotation.Name, // annotation...
+ pta.QualifiedSelection.QualifiedName.ComponentType, // is used in a...
+ pta.Annotation.RequiredComponentType); // but is only valid in a...
+ }
+ else
+ {
+ return string.Format(InspectionResults.ResourceManager.GetString($"{nameof(InvalidAnnotationInspection)}_IncompatibleComponentType", CultureInfo.CurrentUICulture),
+ pta.Annotation.Name, // annotation...
+ pta.QualifiedSelection.QualifiedName.ComponentType); // cannot be used in a...
+ }
+ }
+ }
+}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ApplicationWorksheetFunctionInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ApplicationWorksheetFunctionInspection.cs
index e0f56beaf8..0cecc1f05c 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ApplicationWorksheetFunctionInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ApplicationWorksheetFunctionInspection.cs
@@ -1,12 +1,13 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.InternalApi.Extensions;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -60,7 +61,7 @@ internal class ApplicationWorksheetFunctionInspection : IdentifierReferenceInspe
{
public ApplicationWorksheetFunctionInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override IEnumerable ObjectionableDeclarations(DeclarationFinder finder)
{
@@ -91,7 +92,7 @@ protected override IEnumerable ObjectionableDeclarations(Declaratio
protected override string ResultDescription(IdentifierReference reference)
{
- return string.Format(InspectionResults.ApplicationWorksheetFunctionInspection, reference.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ApplicationWorksheetFunctionInspection), CultureInfo.CurrentUICulture), reference.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ArgumentWithIncompatibleObjectTypeInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ArgumentWithIncompatibleObjectTypeInspection.cs
index 807e65598e..9d4dd00abb 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ArgumentWithIncompatibleObjectTypeInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ArgumentWithIncompatibleObjectTypeInspection.cs
@@ -1,6 +1,4 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.TypeResolvers;
@@ -8,6 +6,9 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -125,7 +126,7 @@ private string SetTypeNameOfExpression(VBAParser.ExpressionContext expression, Q
return _setTypeResolver.SetTypeName(expression, containingModule);
}
- private bool ArgumentPossiblyLegal(Declaration parameterDeclaration , string assignedTypeName)
+ private bool ArgumentPossiblyLegal(Declaration parameterDeclaration, string assignedTypeName)
{
return assignedTypeName == parameterDeclaration.FullAsTypeName
|| assignedTypeName == Tokens.Variant
@@ -163,7 +164,7 @@ protected override string ResultDescription(IdentifierReference reference, strin
var parameterName = reference.Declaration.IdentifierName;
var parameterTypeName = reference.Declaration.FullAsTypeName;
var argumentExpression = reference.Context.GetText();
- return string.Format(InspectionResults.SetAssignmentWithIncompatibleObjectTypeInspection, parameterName, parameterTypeName, argumentExpression, argumentTypeName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(SetAssignmentWithIncompatibleObjectTypeInspection), CultureInfo.CurrentUICulture), parameterName, parameterTypeName, argumentExpression, argumentTypeName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignedByValParameterInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignedByValParameterInspection.cs
index 3d350c7d6e..04d1533379 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignedByValParameterInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignedByValParameterInspection.cs
@@ -1,9 +1,10 @@
-using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -41,19 +42,19 @@ internal sealed class AssignedByValParameterInspection : DeclarationInspectionBa
{
public AssignedByValParameterInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Parameter)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
- return declaration is ParameterDeclaration parameter
- && !parameter.IsByRef
+ return declaration is ParameterDeclaration parameter
+ && !parameter.IsByRef
&& parameter.References
.Any(reference => reference.IsAssignment);
}
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.AssignedByValParameterInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(AssignedByValParameterInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs
index e487e4a47d..51c9455a21 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs
@@ -1,5 +1,3 @@
-using System.Collections.Generic;
-using System.Linq;
using Antlr4.Runtime;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
@@ -12,6 +10,8 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -187,7 +187,7 @@ private static bool IsPotentiallyUsedViaJump(IdentifierReference resultCandidate
|| JumpStmtPotentiallyUsesVariable(resultCandidate, labelIdLineNumberPairs);
}
- private static bool JumpStmtPotentiallyUsesVariable(IdentifierReference resultCandidate, Dictionary labelIdLineNumberPairs) where T: ParserRuleContext
+ private static bool JumpStmtPotentiallyUsesVariable(IdentifierReference resultCandidate, Dictionary labelIdLineNumberPairs) where T : ParserRuleContext
{
if (TryGetRelevantJumpContext(resultCandidate, out var jumpStmt))
{
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs
index 836b21946b..a6ecadf53f 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs
@@ -1,6 +1,4 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Symbols;
@@ -8,6 +6,9 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor.SafeComWrappers;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -45,7 +46,7 @@ internal sealed class AttributeValueOutOfSyncInspection : DeclarationInspectionM
{
public AttributeValueOutOfSyncInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override IEnumerable<(IParseTreeAnnotation Annotation, string AttributeName, IReadOnlyList AttributeValues)> ResultProperties(Declaration declaration, DeclarationFinder finder)
{
@@ -61,7 +62,7 @@ public AttributeValueOutOfSyncInspection(IDeclarationFinderProvider declarationF
{
foreach (var pta in declaration.Annotations)
{
- if (!(pta.Annotation is IAttributeAnnotation annotation)
+ if (!(pta.Annotation is IAttributeAnnotation annotation)
|| !HasDifferingAttributeValues(declaration, pta, out var attributeValues))
{
continue;
@@ -101,7 +102,7 @@ protected override string ResultDescription(Declaration declaration, (IParseTree
{
var (pta, attributeName, attributeValues) = properties;
var annotationName = pta.Annotation.Name;
- return string.Format(InspectionResults.AttributeValueOutOfSyncInspection,
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(AttributeValueOutOfSyncInspection), CultureInfo.CurrentUICulture),
attributeName,
string.Join(", ", attributeValues),
annotationName);
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/BooleanAssignedInIfElseInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/BooleanAssignedInIfElseInspection.cs
index 9ce326bad9..49cb0bdd91 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/BooleanAssignedInIfElseInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/BooleanAssignedInIfElseInspection.cs
@@ -1,9 +1,10 @@
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -46,7 +47,7 @@ public BooleanAssignedInIfElseInspection(IDeclarationFinderProvider declarationF
{
ContextListener = new BooleanAssignedInIfElseListener();
}
-
+
protected override IInspectionListener ContextListener { get; }
protected override string ResultDescription(QualifiedContext context)
@@ -57,9 +58,7 @@ protected override string ResultDescription(QualifiedContext
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ConstantNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ConstantNotUsedInspection.cs
index 2c8508de95..10292f0d8c 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ConstantNotUsedInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ConstantNotUsedInspection.cs
@@ -1,10 +1,11 @@
-using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -40,11 +41,11 @@ internal sealed class ConstantNotUsedInspection : DeclarationInspectionBase
{
public ConstantNotUsedInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Constant)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
- return declaration?.Context != null
+ return declaration?.Context != null
&& !declaration.References.Any()
&& !IsPublicInExposedClass(declaration);
}
@@ -70,7 +71,7 @@ protected override string ResultDescription(Declaration declaration)
var declarationType = declaration.DeclarationType.ToLocalizedString();
var declarationName = declaration.IdentifierName;
return string.Format(
- InspectionResults.IdentifierNotUsedInspection,
+ InspectionResults.ResourceManager.GetString(nameof(InspectionResults.IdentifierNotUsedInspection), CultureInfo.CurrentUICulture),
declarationType,
declarationName);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/DefTypeStatementInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/DefTypeStatementInspection.cs
index 3d141b32f6..6b697912cc 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/DefTypeStatementInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/DefTypeStatementInspection.cs
@@ -1,10 +1,11 @@
-using System.Collections.Generic;
-using Antlr4.Runtime.Misc;
+using Antlr4.Runtime.Misc;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Collections.Generic;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -34,7 +35,7 @@ public DefTypeStatementInspection(IDeclarationFinderProvider declarationFinderPr
{
ContextListener = new DefTypeStatementInspectionListener();
}
-
+
protected override IInspectionListener ContextListener { get; }
protected override string ResultDescription(QualifiedContext context)
@@ -43,7 +44,7 @@ protected override string ResultDescription(QualifiedContext
internal sealed class DuplicatedAnnotationInspection : DeclarationInspectionMultiResultBase
{
- public DuplicatedAnnotationInspection(IDeclarationFinderProvider declarationFinderProvider)
+ public DuplicatedAnnotationInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override IEnumerable ResultProperties(Declaration declaration, DeclarationFinder finder)
{
@@ -54,7 +55,7 @@ protected override IEnumerable ResultProperties(Declaration declara
protected override string ResultDescription(Declaration declaration, IAnnotation annotation)
{
- return string.Format(InspectionResults.DuplicatedAnnotationInspection, annotation);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(DuplicatedAnnotationInspection), CultureInfo.CurrentUICulture), annotation);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyCaseBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyCaseBlockInspection.cs
index c37d80c2ef..44032a4cee 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyCaseBlockInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyCaseBlockInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -52,7 +53,7 @@ public EmptyCaseBlockInspection(IDeclarationFinderProvider declarationFinderProv
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.EmptyCaseBlockInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(EmptyCaseBlockInspection), CultureInfo.CurrentUICulture);
}
private class EmptyCaseBlockListener : EmptyBlockInspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyDoWhileBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyDoWhileBlockInspection.cs
index b012c09cbe..3268e6e605 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyDoWhileBlockInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyDoWhileBlockInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -47,7 +48,7 @@ public EmptyDoWhileBlockInspection(IDeclarationFinderProvider declarationFinderP
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.EmptyDoWhileBlockInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(EmptyDoWhileBlockInspection), CultureInfo.CurrentUICulture);
}
private class EmptyDoWhileBlockListener : EmptyBlockInspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyElseBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyElseBlockInspection.cs
index e981a13f56..6f73663c1f 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyElseBlockInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyElseBlockInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -49,7 +50,7 @@ public EmptyElseBlockInspection(IDeclarationFinderProvider declarationFinderProv
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.EmptyElseBlockInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(EmptyElseBlockInspection), CultureInfo.CurrentUICulture);
}
private class EmptyElseBlockListener : EmptyBlockInspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForEachBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForEachBlockInspection.cs
index f649339fa1..2d8773f8dd 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForEachBlockInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForEachBlockInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -49,7 +50,7 @@ public EmptyForEachBlockInspection(IDeclarationFinderProvider declarationFinderP
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.EmptyForEachBlockInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(EmptyForEachBlockInspection), CultureInfo.CurrentUICulture);
}
private class EmptyForEachBlockListener : EmptyBlockInspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForLoopBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForLoopBlockInspection.cs
index 3c90df6791..d63c20b4cb 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForLoopBlockInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyForLoopBlockInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -49,7 +50,7 @@ public EmptyForLoopBlockInspection(IDeclarationFinderProvider declarationFinderP
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.EmptyForLoopBlockInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(EmptyForLoopBlockInspection), CultureInfo.CurrentUICulture);
}
private class EmptyForLoopBlockListener : EmptyBlockInspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyIfBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyIfBlockInspection.cs
index c0c16f3fd9..8bc2d1855d 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyIfBlockInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyIfBlockInspection.cs
@@ -5,6 +5,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -47,7 +48,7 @@ public EmptyIfBlockInspection(IDeclarationFinderProvider declarationFinderProvid
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.EmptyIfBlockInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(EmptyIfBlockInspection), CultureInfo.CurrentUICulture);
}
protected override IInspectionListener ContextListener { get; }
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyMethodInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyMethodInspection.cs
index baaf3d6688..d93060481c 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyMethodInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyMethodInspection.cs
@@ -1,10 +1,11 @@
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
+using Rubberduck.Parsing;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
-using Rubberduck.Parsing;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -37,12 +38,12 @@ internal sealed class EmptyMethodInspection : DeclarationInspectionBase
{
public EmptyMethodInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Member)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
- return declaration is ModuleBodyElementDeclaration member
- && !member.IsInterfaceMember
+ return declaration is ModuleBodyElementDeclaration member
+ && !member.IsInterfaceMember
&& !member.Block.ContainsExecutableStatements();
}
@@ -52,7 +53,7 @@ protected override string ResultDescription(Declaration member)
var declarationType = member.DeclarationType.ToLocalizedString();
return string.Format(
- InspectionResults.EmptyMethodInspection,
+ InspectionResults.ResourceManager.GetString(nameof(EmptyMethodInspection), CultureInfo.CurrentUICulture),
declarationType,
identifierName);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyModuleInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyModuleInspection.cs
index fc99597114..5c87dd8473 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyModuleInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyModuleInspection.cs
@@ -1,11 +1,12 @@
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Parsing.VBA.Parsing;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -21,7 +22,7 @@ internal sealed class EmptyModuleInspection : DeclarationInspectionBase
private readonly IParseTreeProvider _parseTreeProvider;
public EmptyModuleInspection(IDeclarationFinderProvider declarationFinderProvider, IParseTreeProvider parseTreeProvider)
- : base(declarationFinderProvider, new []{DeclarationType.Module}, new []{DeclarationType.Document})
+ : base(declarationFinderProvider, new[] { DeclarationType.Module }, new[] { DeclarationType.Document })
{
_emptyModuleVisitor = new EmptyModuleVisitor();
_parseTreeProvider = parseTreeProvider;
@@ -37,7 +38,7 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.EmptyModuleInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(EmptyModuleInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyStringLiteralInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyStringLiteralInspection.cs
index 98868b1c06..5fbae40e7c 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyStringLiteralInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyStringLiteralInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -10,7 +11,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
/// Flags uses of an empty string literal ("").
///
///
- /// Treating an empty string literal as equal to the 'vbNullString' constant
+ /// In the context of a unit test, treating an empty string literal as equal to the 'vbNullString' constant
/// requires using the PermissiveAssertClass. The default AssertClass is more strict about data types, and tells them apart.
///
///
@@ -53,7 +54,7 @@ public EmptyStringLiteralInspection(IDeclarationFinderProvider declarationFinder
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.EmptyStringLiteralInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(EmptyStringLiteralInspection), CultureInfo.CurrentUICulture);
}
private class EmptyStringLiteralListener : InspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyWhileWendBlockInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyWhileWendBlockInspection.cs
index 8952b539db..41f293e5b0 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyWhileWendBlockInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyWhileWendBlockInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -47,7 +48,7 @@ public EmptyWhileWendBlockInspection(IDeclarationFinderProvider declarationFinde
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.EmptyWhileWendBlockInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(EmptyWhileWendBlockInspection), CultureInfo.CurrentUICulture);
}
private class EmptyWhileWendBlockListener : EmptyBlockInspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/EncapsulatePublicFieldInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/EncapsulatePublicFieldInspection.cs
index 125c8de40f..6d3633c682 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/EncapsulatePublicFieldInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/EncapsulatePublicFieldInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -35,7 +36,7 @@ internal sealed class EncapsulatePublicFieldInspection : DeclarationInspectionBa
{
public EncapsulatePublicFieldInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Variable)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -47,7 +48,7 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.EncapsulatePublicFieldInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(EncapsulatePublicFieldInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelMemberMayReturnNothingInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelMemberMayReturnNothingInspection.cs
index 36558288fd..dca278261f 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelMemberMayReturnNothingInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelMemberMayReturnNothingInspection.cs
@@ -1,11 +1,12 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -47,7 +48,7 @@ internal class ExcelMemberMayReturnNothingInspection : MemberAccessMayReturnNoth
{
public ExcelMemberMayReturnNothingInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
private static readonly List<(string className, string memberName)> ExcelMembers = new List<(string className, string memberName)>
{
@@ -77,6 +78,6 @@ public override IEnumerable MembersUnderTest(DeclarationFinder find
.Where(member => ExcelMembers.Contains((member.ComponentName, member.IdentifierName)));
}
- public override string ResultTemplate => InspectionResults.ExcelMemberMayReturnNothingInspection;
+ public override string ResultTemplate => InspectionResults.ResourceManager.GetString(nameof(ExcelMemberMayReturnNothingInspection), CultureInfo.CurrentUICulture);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelUdfNameIsValidCellReferenceInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelUdfNameIsValidCellReferenceInspection.cs
index 3d2ecca94b..a0a3edb9ac 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelUdfNameIsValidCellReferenceInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelUdfNameIsValidCellReferenceInspection.cs
@@ -1,8 +1,4 @@
-using System;
-using System.Collections.Generic;
-using System.Linq;
-using System.Text.RegularExpressions;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
@@ -10,6 +6,11 @@
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
using Rubberduck.VBEditor.SafeComWrappers;
+using System;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
+using System.Text.RegularExpressions;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -41,8 +42,8 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
internal class ExcelUdfNameIsValidCellReferenceInspection : DeclarationInspectionUsingGlobalInformationBase
{
public ExcelUdfNameIsValidCellReferenceInspection(IDeclarationFinderProvider declarationFinderProvider)
- : base(declarationFinderProvider, new []{DeclarationType.Function}, new []{DeclarationType.PropertyGet, DeclarationType.LibraryFunction})
- {}
+ : base(declarationFinderProvider, new[] { DeclarationType.Function }, new[] { DeclarationType.PropertyGet, DeclarationType.LibraryFunction })
+ { }
protected override IEnumerable DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder, bool excelIsReferenced)
{
@@ -96,7 +97,7 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.ExcelUdfNameIsValidCellReferenceInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ExcelUdfNameIsValidCellReferenceInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueAlwaysDiscardedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueAlwaysDiscardedInspection.cs
index 46fc854b83..79b98de9e1 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueAlwaysDiscardedInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueAlwaysDiscardedInspection.cs
@@ -1,6 +1,4 @@
-using System.Collections.Generic;
-using System.Linq;
-using Antlr4.Runtime;
+using Antlr4.Runtime;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.InternalApi.Extensions;
using Rubberduck.Parsing;
@@ -9,6 +7,9 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -55,7 +56,7 @@ internal sealed class FunctionReturnValueAlwaysDiscardedInspection : Declaration
{
public FunctionReturnValueAlwaysDiscardedInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Function)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -168,7 +169,7 @@ private static bool IsCalledAsProcedure(ParserRuleContext context)
protected override string ResultDescription(Declaration declaration)
{
var functionName = declaration.QualifiedName.ToString();
- return string.Format(InspectionResults.FunctionReturnValueAlwaysDiscardedInspection, functionName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(FunctionReturnValueAlwaysDiscardedInspection), CultureInfo.CurrentUICulture), functionName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueDiscardedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueDiscardedInspection.cs
index 2ac32ca6b4..4ba1cd7923 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueDiscardedInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueDiscardedInspection.cs
@@ -6,6 +6,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -91,7 +92,7 @@ private static bool IsCalledAsProcedure(ParserRuleContext context)
//This case is necessary if the context is itself the unrestricted identifier in a member access.
var furtherMemberAccessParent = memberAccessParent.GetAncestor();
if (furtherMemberAccessParent != null)
- {
+ {
return false;
}
}
@@ -104,7 +105,7 @@ private static bool IsCalledAsProcedure(ParserRuleContext context)
protected override string ResultDescription(IdentifierReference reference)
{
var functionName = reference.Declaration.QualifiedName.ToString();
- return string.Format(InspectionResults.FunctionReturnValueDiscardedInspection, functionName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(FunctionReturnValueDiscardedInspection), CultureInfo.CurrentUICulture), functionName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/HostSpecificExpressionInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/HostSpecificExpressionInspection.cs
index 01dea2befd..06f84d06b1 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/HostSpecificExpressionInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/HostSpecificExpressionInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -35,7 +36,7 @@ internal sealed class HostSpecificExpressionInspection : DeclarationInspectionBa
{
public HostSpecificExpressionInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.BracketedExpression)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -44,7 +45,7 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.HostSpecificExpressionInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(HostSpecificExpressionInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/HungarianNotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/HungarianNotationInspection.cs
index fb699e51a5..8a1a783808 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/HungarianNotationInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/HungarianNotationInspection.cs
@@ -1,6 +1,4 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.CodeAnalysis.Settings;
using Rubberduck.Common;
@@ -8,6 +6,9 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.SettingsProvider;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -49,7 +50,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
///
internal sealed class HungarianNotationInspection : DeclarationInspectionUsingGlobalInformationBase>
{
- private static readonly DeclarationType[] TargetDeclarationTypes = new []
+ private static readonly DeclarationType[] TargetDeclarationTypes = new[]
{
DeclarationType.Parameter,
DeclarationType.Constant,
@@ -65,7 +66,7 @@ internal sealed class HungarianNotationInspection : DeclarationInspectionUsingGl
DeclarationType.Variable
};
- private static readonly DeclarationType[] IgnoredProcedureTypes = new []
+ private static readonly DeclarationType[] IgnoredProcedureTypes = new[]
{
DeclarationType.LibraryFunction,
DeclarationType.LibraryProcedure
@@ -79,19 +80,22 @@ public HungarianNotationInspection(IDeclarationFinderProvider declarationFinderP
_settings = settings;
}
+ private CodeInspectionSettings _configuration;
+
protected override List GlobalInformation(DeclarationFinder finder)
{
- var settings = _settings.Read();
- return settings.WhitelistedIdentifiers
+ _configuration = _settings.Read();
+ return _configuration.WhitelistedIdentifiers
.Select(s => s.Identifier)
.ToList();
}
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder, List whitelistedNames)
{
- return !whitelistedNames.Contains(declaration.IdentifierName)
- && !IgnoredProcedureTypes.Contains(declaration.ParentDeclaration.DeclarationType)
- && declaration.IdentifierName.TryMatchHungarianNotationCriteria(out _);
+ return (_configuration.IgnoreFormControlsHungarianNotation && declaration.DeclarationType == DeclarationType.Control) ||
+ (!whitelistedNames.Contains(declaration.IdentifierName)
+ && !IgnoredProcedureTypes.Contains(declaration.ParentDeclaration.DeclarationType)
+ && declaration.IdentifierName.TryMatchHungarianNotationCriteria(out _));
}
protected override string ResultDescription(Declaration declaration)
@@ -99,7 +103,7 @@ protected override string ResultDescription(Declaration declaration)
var declarationType = declaration.DeclarationType.ToLocalizedString();
var declarationName = declaration.IdentifierName;
return string.Format(
- Resources.Inspections.InspectionResults.IdentifierNameInspection,
+ Resources.Inspections.InspectionResults.ResourceManager.GetString(nameof(Resources.Inspections.InspectionResults.IdentifierNameInspection), CultureInfo.CurrentUICulture),
declarationType,
declarationName);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IIfSideEffectInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IIfSideEffectInspection.cs
index 8c0908c631..153c892475 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IIfSideEffectInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IIfSideEffectInspection.cs
@@ -8,6 +8,7 @@
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
using System.Collections.Generic;
+using System.Globalization;
using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
@@ -119,7 +120,7 @@ public IIfSideEffectInspection(IDeclarationFinderProvider declarationFinderProvi
protected override IEnumerable DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
{
var iifReferences = _declarationFinderProvider.DeclarationFinder.BuiltInDeclarations(DeclarationType.Function)
- .SingleOrDefault(d => string.Compare( d.IdentifierName, "IIf", System.StringComparison.InvariantCultureIgnoreCase) == 0)
+ .SingleOrDefault(d => string.Compare(d.IdentifierName, "IIf", System.StringComparison.InvariantCultureIgnoreCase) == 0)
.References.Where(rf => rf.QualifiedModuleName == module);
if (!iifReferences.Any())
@@ -178,7 +179,7 @@ private static VBAParser.ArgumentContext ExtractArgumentContext(IEnumerable ctxt.children.OfType())
//'ToUpperInvariant' in case the user has (at some point) entered a declaration that re-cased any IIf parameter names
.ToDictionary(ch => ch.GetText().ToUpperInvariant());
-
+
if (unrestrictedIDContextsByName.TryGetValue(partParam.Identifier.ToUpperInvariant(), out var expressionUnrestrictedIDContext))
{
return expressionUnrestrictedIDContext.Parent.Parent as VBAParser.ArgumentContext;
@@ -190,7 +191,7 @@ private static VBAParser.ArgumentContext ExtractArgumentContext(IEnumerable
@@ -199,7 +200,7 @@ protected override string ResultDescription(IdentifierReference reference)
///
private static Dictionary CreateLibraryFunctionIdentifiersToIgnore()
{
- return LoadLibraryFunctionIdentifiersToIgnore( new Dictionary(),
+ return LoadLibraryFunctionIdentifiersToIgnore(new Dictionary(),
//MS-VBAL 6.1.2.3 Conversion Module
/*Excluded for potential of raising errors:
* "CBool", "CByte", "CCur", "CDate", "CVDate", "CDbl", "CDec", "CInt", "CLng", "CLngLng", "ClngPtr",
@@ -224,7 +225,7 @@ private static Dictionary CreateLibraryFunctionIdentifiersToIgno
*/
//MS-VBAL 6.1.2.7 Information
- "IMEStatus", "IsArray", "IsDate", "IsEmpty", "IsError", "IsMissing", "IsNull", "IsNumeric", "IsObject",
+ "IMEStatus", "IsArray", "IsDate", "IsEmpty", "IsError", "IsMissing", "IsNull", "IsNumeric", "IsObject",
"QBColor", "RGB", "TypeName", "VarType",
//MS-VBAL 6.1.2.8 Interaction
@@ -248,7 +249,7 @@ private static Dictionary CreateLibraryFunctionIdentifiersToIgno
* "Right$", "RightB$", "Asc", "AscW", "AscB", "Chr", "Chr$", "ChB", "ChB$", "ChrW", "ChrW$", "Filter",
* "MonthName", "WeekdayName", "Space", "Space$", "Split","StrConv", "String", "String$"
*/
- "LCase", "LCase$", "Len", "LenB", "Trim", "LTrim", "RTrim", "Trim$", "LTrim$", "RTrim$", "StrComp",
+ "LCase", "LCase$", "Len", "LenB", "Trim", "LTrim", "RTrim", "Trim$", "LTrim$", "RTrim$", "StrComp",
"StrReverse", "UCase", "UCase$"
);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplementedInterfaceMemberInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplementedInterfaceMemberInspection.cs
index 0ceadcaaf0..2081790bb6 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplementedInterfaceMemberInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplementedInterfaceMemberInspection.cs
@@ -1,5 +1,4 @@
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Common;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Annotations.Concrete;
@@ -7,6 +6,8 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -44,7 +45,7 @@ internal sealed class ImplementedInterfaceMemberInspection : DeclarationInspecti
{
public ImplementedInterfaceMemberInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.ClassModule)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -74,12 +75,12 @@ protected override string ResultDescription(Declaration declaration)
{
var qualifiedName = declaration.QualifiedModuleName.ToString();
var declarationType = CodeAnalysisUI.ResourceManager
- .GetString("DeclarationType_" + declaration.DeclarationType)
+ .GetString("DeclarationType_" + declaration.DeclarationType, CultureInfo.CurrentUICulture)
.Capitalize();
var identifierName = declaration.IdentifierName;
return string.Format(
- InspectionResults.ImplementedInterfaceMemberInspection,
+ InspectionResults.ResourceManager.GetString(nameof(ImplementedInterfaceMemberInspection), CultureInfo.CurrentUICulture),
qualifiedName,
declarationType,
identifierName);
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveSheetReferenceInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveSheetReferenceInspection.cs
index f7369c6930..6a0f3f8ac6 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveSheetReferenceInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveSheetReferenceInspection.cs
@@ -1,10 +1,11 @@
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -45,7 +46,7 @@ internal sealed class ImplicitActiveSheetReferenceInspection : ImplicitSheetRefe
{
public ImplicitActiveSheetReferenceInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override string[] GlobalObjectClassNames => new[] { "Global", "_Global", };
@@ -58,7 +59,7 @@ protected override bool IsResultReference(IdentifierReference reference, Declara
protected override string ResultDescription(IdentifierReference reference)
{
return string.Format(
- InspectionResults.ImplicitActiveSheetReferenceInspection,
+ InspectionResults.ResourceManager.GetString(nameof(ImplicitActiveSheetReferenceInspection), CultureInfo.CurrentUICulture),
reference.Declaration.IdentifierName);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveWorkbookReferenceInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveWorkbookReferenceInspection.cs
index 61279d1e08..f4a3e28318 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveWorkbookReferenceInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveWorkbookReferenceInspection.cs
@@ -1,10 +1,11 @@
-using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -67,8 +68,8 @@ protected override bool IsResultReference(IdentifierReference reference, Declara
var excelProjectId = Excel(finder).ProjectId;
var applicationCandidates = finder.MatchName("Application")
- .Where(m => m.ProjectId.Equals(excelProjectId)
- && ( m.DeclarationType == DeclarationType.PropertyGet
+ .Where(m => m.ProjectId.Equals(excelProjectId)
+ && (m.DeclarationType == DeclarationType.PropertyGet
|| m.DeclarationType == DeclarationType.ClassModule));
var qualifyingDeclaration = reference.QualifyingReference.Declaration;
@@ -80,7 +81,7 @@ protected override bool IsResultReference(IdentifierReference reference, Declara
protected override string ResultDescription(IdentifierReference reference)
{
var referenceText = reference.Context.GetText();
- return string.Format(InspectionResults.ImplicitActiveWorkbookReferenceInspection, referenceText);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ImplicitActiveWorkbookReferenceInspection), CultureInfo.CurrentUICulture), referenceText);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitByRefModifierInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitByRefModifierInspection.cs
index 9c968f697a..c3433b553d 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitByRefModifierInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitByRefModifierInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
@@ -49,7 +50,7 @@ internal sealed class ImplicitByRefModifierInspection : DeclarationInspectionBas
{
public ImplicitByRefModifierInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Parameter)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -70,14 +71,14 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
private static bool IsPropertyMutatorRHSParameter(ModuleBodyElementDeclaration enclosingMethod, ParameterDeclaration implicitByRefParameter)
{
return (enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertyLet)
- || enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertySet))
+ || enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertySet))
&& enclosingMethod.Parameters.Last().Equals(implicitByRefParameter);
}
protected override string ResultDescription(Declaration declaration)
{
return string.Format(
- InspectionResults.ImplicitByRefModifierInspection,
+ InspectionResults.ResourceManager.GetString(nameof(ImplicitByRefModifierInspection), CultureInfo.CurrentUICulture),
declaration.IdentifierName);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitContainingWorkbookReferenceInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitContainingWorkbookReferenceInspection.cs
index 0c705b86de..5212c0b9ad 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitContainingWorkbookReferenceInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitContainingWorkbookReferenceInspection.cs
@@ -1,11 +1,12 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -67,7 +68,7 @@ protected override string ResultDescription(IdentifierReference reference)
{
var referenceText = reference.Context.GetText();
return string.Format(
- InspectionResults.ImplicitContainingWorkbookReferenceInspection,
+ InspectionResults.ResourceManager.GetString(nameof(ImplicitContainingWorkbookReferenceInspection), CultureInfo.CurrentUICulture),
referenceText);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitContainingWorksheetReferenceInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitContainingWorksheetReferenceInspection.cs
index 0ce1d79361..c902e9421c 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitContainingWorksheetReferenceInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitContainingWorksheetReferenceInspection.cs
@@ -1,10 +1,11 @@
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -41,7 +42,7 @@ internal sealed class ImplicitContainingWorksheetReferenceInspection : ImplicitS
{
public ImplicitContainingWorksheetReferenceInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
{
@@ -53,7 +54,7 @@ protected override bool IsResultReference(IdentifierReference reference, Declara
protected override string ResultDescription(IdentifierReference reference)
{
return string.Format(
- InspectionResults.ImplicitContainingWorksheetReferenceInspection,
+ InspectionResults.ResourceManager.GetString(nameof(ImplicitContainingWorksheetReferenceInspection), CultureInfo.CurrentUICulture),
reference.Declaration.IdentifierName);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAccessInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAccessInspection.cs
index e59feed6d0..e502ac69da 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAccessInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAccessInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -75,7 +76,7 @@ protected override string ResultDescription(IdentifierReference reference)
{
var expression = reference.IdentifierName;
var defaultMember = reference.Declaration.QualifiedName.ToString();
- return string.Format(InspectionResults.ImplicitDefaultMemberAccessInspection, expression, defaultMember);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ImplicitDefaultMemberAccessInspection), CultureInfo.CurrentUICulture), expression, defaultMember);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitPublicMemberInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitPublicMemberInspection.cs
index 6bee81f94c..304ceaf678 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitPublicMemberInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitPublicMemberInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -36,7 +37,7 @@ internal sealed class ImplicitPublicMemberInspection : DeclarationInspectionBase
public ImplicitPublicMemberInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, ProcedureTypes) { }
- private static readonly DeclarationType[] ProcedureTypes =
+ private static readonly DeclarationType[] ProcedureTypes =
{
DeclarationType.Function,
DeclarationType.Procedure,
@@ -54,7 +55,7 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.ImplicitPublicMemberInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ImplicitPublicMemberInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitRecursiveDefaultMemberAccessInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitRecursiveDefaultMemberAccessInspection.cs
index f7e76471d1..f4536c1ef1 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitRecursiveDefaultMemberAccessInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitRecursiveDefaultMemberAccessInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -87,7 +88,7 @@ protected override string ResultDescription(IdentifierReference reference)
{
var expression = reference.IdentifierName;
var defaultMember = reference.Declaration.QualifiedName.ToString();
- return string.Format(InspectionResults.ImplicitRecursiveDefaultMemberAccessInspection, expression, defaultMember);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ImplicitRecursiveDefaultMemberAccessInspection), CultureInfo.CurrentUICulture), expression, defaultMember);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitUnboundDefaultMemberAccessInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitUnboundDefaultMemberAccessInspection.cs
index 4d5fae59a4..c037f16694 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitUnboundDefaultMemberAccessInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitUnboundDefaultMemberAccessInspection.cs
@@ -1,11 +1,12 @@
-using System.Collections.Generic;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -81,7 +82,7 @@ protected override bool IsResultReference(IdentifierReference reference, Declara
protected override string ResultDescription(IdentifierReference reference)
{
var expression = reference.IdentifierName;
- return string.Format(InspectionResults.ImplicitUnboundDefaultMemberAccessInspection, expression);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ImplicitUnboundDefaultMemberAccessInspection), CultureInfo.CurrentUICulture), expression);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitVariantReturnTypeInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitVariantReturnTypeInspection.cs
index 1130c7d5c0..797258908c 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitVariantReturnTypeInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitVariantReturnTypeInspection.cs
@@ -2,6 +2,7 @@
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -33,11 +34,11 @@ internal sealed class ImplicitVariantReturnTypeInspection : ImplicitTypeInspecti
{
public ImplicitVariantReturnTypeInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Function)
- {}
+ { }
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.ImplicitVariantReturnTypeInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ImplicitVariantReturnTypeInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitlyTypedConstInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitlyTypedConstInspection.cs
index 5696f45c33..5cb307dd95 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitlyTypedConstInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitlyTypedConstInspection.cs
@@ -2,6 +2,7 @@
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -36,11 +37,11 @@ internal sealed class ImplicitlyTypedConstInspection : ImplicitTypeInspectionBas
{
public ImplicitlyTypedConstInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Constant)
- {}
+ { }
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.ImplicitlyTypedConstInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ImplicitlyTypedConstInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/InconsistentArrayBaseInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/InconsistentArrayBaseInspection.cs
new file mode 100644
index 0000000000..ffb3392a45
--- /dev/null
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/InconsistentArrayBaseInspection.cs
@@ -0,0 +1,83 @@
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.Parsing;
+using Rubberduck.Parsing.Grammar;
+using Rubberduck.Parsing.Symbols;
+using Rubberduck.Parsing.VBA;
+using Rubberduck.Parsing.VBA.DeclarationCaching;
+using Rubberduck.Resources.Inspections;
+using System.Globalization;
+
+namespace Rubberduck.CodeAnalysis.Inspections.Concrete
+{
+ ///
+ /// Warns about inconsistent implicit lower bounds of VBA.Array arrays when 'Option Base 1' is specified.
+ ///
+ ///
+ /// The base of an array obtained from a qualified 'VBA.Array' function call is always zero, regardless of any 'Option Base' setting.
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ internal class InconsistentArrayBaseInspection : IdentifierReferenceInspectionBase
+ {
+ public InconsistentArrayBaseInspection(IDeclarationFinderProvider declarationFinderProvider)
+ : base(declarationFinderProvider)
+ {
+ }
+
+ protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
+ {
+ var hasOptionBase1 = reference.Context
+ .GetAncestor()
+ .GetDescendent()?
+ .numberLiteral()?.GetText() == "1";
+
+ if (hasOptionBase1 && reference.Declaration.ProjectName == "VBA" && reference.Declaration.IdentifierName == "Array")
+ {
+ if (reference.QualifyingReference?.Declaration.IdentifierName == "VBA")
+ {
+ return true;
+ }
+ }
+
+ return false;
+ }
+
+ protected override string ResultDescription(IdentifierReference reference)
+ {
+ // reference.Declaration is the VBA.Array function
+ // we could inspect the context to find a possible LHS variable being assigned, but VBA.Array could also be an argument
+ // so it's not a given that there's a relevant identifier to call out, so the resource string does not have any placeholders.
+ return InspectionResults.ResourceManager.GetString(nameof(InconsistentArrayBaseInspection), CultureInfo.CurrentUICulture);
+ }
+ }
+}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/InconsistentParamArrayBaseInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/InconsistentParamArrayBaseInspection.cs
new file mode 100644
index 0000000000..807fafb4bf
--- /dev/null
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/InconsistentParamArrayBaseInspection.cs
@@ -0,0 +1,87 @@
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.Parsing;
+using Rubberduck.Parsing.Grammar;
+using Rubberduck.Parsing.Symbols;
+using Rubberduck.Parsing.VBA;
+using Rubberduck.Parsing.VBA.DeclarationCaching;
+using Rubberduck.Resources.Inspections;
+using System.Globalization;
+
+namespace Rubberduck.CodeAnalysis.Inspections.Concrete
+{
+
+ ///
+ /// Warns about inconsistent implicit lower bounds of ParamArray arrays when 'Option Base 1' is specified.
+ ///
+ ///
+ /// The base of a ParamArray is always zero, regardless of any 'Option Base' setting.
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ internal sealed class InconsistentParamArrayBaseInspection : DeclarationInspectionBase
+ {
+ public InconsistentParamArrayBaseInspection(IDeclarationFinderProvider declarationFinderProvider)
+ : base(declarationFinderProvider)
+ {
+ }
+
+ protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
+ {
+ var hasOptionBase1 = declaration.Context
+ .GetAncestor()
+ .GetDescendent()?
+ .numberLiteral()?.GetText() == "1";
+
+
+ if (hasOptionBase1 && declaration is ParameterDeclaration parameter)
+ {
+ return parameter.IsParamArray;
+ }
+
+ return false;
+ }
+
+ protected override string ResultDescription(Declaration declaration)
+ {
+ // declaration is the ParamArray parameter
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(InconsistentParamArrayBaseInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
+ }
+ }
+}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedDefaultMemberAccessInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedDefaultMemberAccessInspection.cs
index 096e98853b..57f8ccf842 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedDefaultMemberAccessInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedDefaultMemberAccessInspection.cs
@@ -5,6 +5,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -54,7 +55,7 @@ protected override string ResultDescription(IdentifierReference reference)
{
var expression = reference.IdentifierName;
var defaultMember = reference.Declaration.QualifiedName.ToString();
- return string.Format(InspectionResults.IndexedDefaultMemberAccessInspection, expression, defaultMember);
+ return string.Format(InspectionResults.ResourceManager.GetString("IndexedDefaultMemberAccessInspection", CultureInfo.CurrentUICulture), expression, defaultMember);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedRecursiveDefaultMemberAccessInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedRecursiveDefaultMemberAccessInspection.cs
index 679d8e3caf..e6b7961047 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedRecursiveDefaultMemberAccessInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedRecursiveDefaultMemberAccessInspection.cs
@@ -5,6 +5,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -54,7 +55,7 @@ protected override string ResultDescription(IdentifierReference reference)
{
var expression = reference.IdentifierName;
var defaultMember = reference.Declaration.QualifiedName.ToString();
- return string.Format(InspectionResults.IndexedRecursiveDefaultMemberAccessInspection, expression, defaultMember);
+ return string.Format(InspectionResults.ResourceManager.GetString("IndexedRecursiveDefaultMemberAccessInspection", CultureInfo.CurrentUICulture), expression, defaultMember);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedUnboundDefaultMemberAccessInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedUnboundDefaultMemberAccessInspection.cs
index 78686793e6..73bc3f5105 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedUnboundDefaultMemberAccessInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IndexedUnboundDefaultMemberAccessInspection.cs
@@ -1,5 +1,4 @@
-using System.Collections.Generic;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
@@ -7,6 +6,8 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -60,7 +61,7 @@ protected override bool IsResultReference(IdentifierReference reference, Declara
protected override string ResultDescription(IdentifierReference reference)
{
var expression = reference.IdentifierName;
- return string.Format(InspectionResults.IndexedUnboundDefaultMemberAccessInspection, expression);
+ return string.Format(InspectionResults.ResourceManager.GetString("IndexedUnboundDefaultMemberAccessInspection", CultureInfo.CurrentUICulture), expression);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IntegerDataTypeInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IntegerDataTypeInspection.cs
index df7771681a..4f015fa855 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IntegerDataTypeInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IntegerDataTypeInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -38,7 +39,7 @@ internal sealed class IntegerDataTypeInspection : DeclarationInspectionBase
{
public IntegerDataTypeInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -82,7 +83,7 @@ protected override string ResultDescription(Declaration declaration)
var declarationType = declaration.DeclarationType.ToLocalizedString();
var declarationName = declaration.IdentifierName;
return string.Format(
- Resources.Inspections.InspectionResults.IntegerDataTypeInspection,
+ Resources.Inspections.InspectionResults.ResourceManager.GetString(nameof(IntegerDataTypeInspection), CultureInfo.CurrentUICulture),
declarationType,
declarationName);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/InvalidAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/InvalidAnnotationInspection.cs
index 9b53d9ab4c..78f107d05d 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/InvalidAnnotationInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/InvalidAnnotationInspection.cs
@@ -1,180 +1,15 @@
-using System;
-using System.Collections.Generic;
-using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
-using Rubberduck.CodeAnalysis.Inspections.Results;
using Rubberduck.InternalApi.Extensions;
-using Rubberduck.Parsing;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
-using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
-using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
- ///
- /// An inspection that flags invalid annotation comments.
- ///
- internal abstract class InvalidAnnotationInspectionBase : InspectionBase
- {
- protected InvalidAnnotationInspectionBase(IDeclarationFinderProvider declarationFinderProvider)
- : base(declarationFinderProvider) { }
-
- protected QualifiedContext Context(IParseTreeAnnotation pta) =>
- new QualifiedContext(pta.QualifiedSelection.QualifiedName, pta.Context);
-
- protected sealed override IEnumerable DoGetInspectionResults(DeclarationFinder finder)
- {
- return finder.UserDeclarations(DeclarationType.Module)
-.Where(module => module != null)
-.SelectMany(module => DoGetInspectionResults(module.QualifiedModuleName, finder));
- }
-
- protected IInspectionResult InspectionResult(IParseTreeAnnotation pta) =>
- new QualifiedContextInspectionResult(this, ResultDescription(pta), Context(pta));
-
- ///
- /// Gets all invalid annotations covered by this inspection.
- ///
- /// All user code annotations.
- /// All user declarations.
- /// All identifier references in user code.
- ///
- protected abstract IEnumerable GetInvalidAnnotations(
- IEnumerable annotations,
- IEnumerable userDeclarations,
- IEnumerable identifierReferences);
-
- ///
- /// Gets an annotation-specific description for an inspection result.
- ///
- /// The invalid annotation.
- ///
- protected abstract string ResultDescription(IParseTreeAnnotation pta);
-
- protected sealed override IEnumerable DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
- {
- var annotations = finder.FindAnnotations(module);
- var userDeclarations = finder.Members(module).ToList();
- var identifierReferences = finder.IdentifierReferences(module).ToList();
-
- var invalidAnnotations = GetInvalidAnnotations(annotations, userDeclarations, identifierReferences);
- return invalidAnnotations.Select(InspectionResult).ToList();
- }
- }
-
- ///
- /// Flags comments that parsed like Rubberduck annotations, but were not recognized as such.
- ///
- ///
- /// Other add-ins may support similar-looking annotations that Rubberduck does not recognize; this inspection can be used to spot a typo in Rubberduck annotations.
- ///
- ///
- ///
- ///
- ///
- ///
- ///
- ///
- ///
- ///
- ///
- internal sealed class UnrecognizedAnnotationInspection : InvalidAnnotationInspectionBase
- {
- public UnrecognizedAnnotationInspection(IDeclarationFinderProvider declarationFinderProvider)
- : base(declarationFinderProvider) { }
-
- protected override IEnumerable GetInvalidAnnotations(
- IEnumerable annotations,
- IEnumerable userDeclarations,
- IEnumerable identifierReferences)
- {
- return annotations.Where(pta => pta.Annotation is NotRecognizedAnnotation).ToList();
- }
-
- protected override string ResultDescription(IParseTreeAnnotation pta) =>
- string.Format(InspectionResults.UnrecognizedAnnotationInspection, pta.Context.GetText());
- }
-
- ///
- /// Flags Rubberduck annotations used in a component type that is incompatible with that annotation.
- ///
- ///
- /// Some annotations can only be used in a specific type of module; others cannot be used in certain types of modules.
- ///
- ///
- ///
- ///
- ///
- ///
- ///
- ///
- ///
- ///
- ///
- internal sealed class AnnotationInIncompatibleComponentTypeInspection : InvalidAnnotationInspectionBase
- {
- public AnnotationInIncompatibleComponentTypeInspection(IDeclarationFinderProvider declarationFinderProvider)
- : base(declarationFinderProvider) { }
-
- protected override IEnumerable GetInvalidAnnotations(
- IEnumerable annotations,
- IEnumerable userDeclarations,
- IEnumerable identifierReferences)
- {
- foreach (var pta in annotations)
- {
- var annotation = pta.Annotation;
- var componentType = pta.QualifiedSelection.QualifiedName.ComponentType;
- if (annotation.RequiredComponentType.HasValue && annotation.RequiredComponentType != componentType
- || annotation.IncompatibleComponentTypes.Contains(componentType))
- {
- yield return pta;
- }
- }
-
- yield break;
- }
-
- protected override string ResultDescription(IParseTreeAnnotation pta)
- {
- if (pta.Annotation.RequiredComponentType.HasValue)
- {
- return string.Format(InspectionResults.InvalidAnnotationInspection_NotInRequiredComponentType,
- pta.Annotation.Name, // annotation...
- pta.QualifiedSelection.QualifiedName.ComponentType, // is used in a...
- pta.Annotation.RequiredComponentType); // but is only valid in a...
- }
- else
- {
- return string.Format(InspectionResults.InvalidAnnotationInspection_IncompatibleComponentType,
- pta.Annotation.Name, // annotation...
- pta.QualifiedSelection.QualifiedName.ComponentType); // cannot be used in a...
- }
- }
- }
///
/// Flags invalid or misplaced Rubberduck annotation comments.
@@ -210,10 +45,10 @@ internal sealed class InvalidAnnotationInspection : InvalidAnnotationInspectionB
{
public InvalidAnnotationInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override string ResultDescription(IParseTreeAnnotation pta) =>
- string.Format(InspectionResults.InvalidAnnotationInspection, pta.Annotation.Name);
+ string.Format(InspectionResults.ResourceManager.GetString(nameof(InvalidAnnotationInspection), CultureInfo.CurrentUICulture), pta.Annotation.Name);
protected override IEnumerable GetInvalidAnnotations(
IEnumerable annotations,
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingOnInappropriateArgumentInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingOnInappropriateArgumentInspection.cs
index a4baac3aff..d89a038117 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingOnInappropriateArgumentInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingOnInappropriateArgumentInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -38,7 +39,7 @@ internal class IsMissingOnInappropriateArgumentInspection : IsMissingInspectionB
{
public IsMissingOnInappropriateArgumentInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override (bool isResult, ParameterDeclaration properties) IsUnsuitableArgumentWithAdditionalProperties(ArgumentReference reference, DeclarationFinder finder)
{
@@ -54,7 +55,7 @@ protected override (bool isResult, ParameterDeclaration properties) IsUnsuitable
protected override string ResultDescription(IdentifierReference reference, ParameterDeclaration parameter)
{
- return InspectionResults.IsMissingOnInappropriateArgumentInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(IsMissingOnInappropriateArgumentInspection), CultureInfo.CurrentUICulture);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingWithNonArgumentParameterInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingWithNonArgumentParameterInspection.cs
index 8143f50bcb..ec05267cba 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingWithNonArgumentParameterInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IsMissingWithNonArgumentParameterInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -38,7 +39,7 @@ internal class IsMissingWithNonArgumentParameterInspection : IsMissingInspection
{
public IsMissingWithNonArgumentParameterInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override (bool isResult, ParameterDeclaration properties) IsUnsuitableArgumentWithAdditionalProperties(ArgumentReference reference, DeclarationFinder finder)
{
@@ -49,7 +50,7 @@ protected override (bool isResult, ParameterDeclaration properties) IsUnsuitable
protected override string ResultDescription(IdentifierReference reference, ParameterDeclaration properties)
{
- return InspectionResults.IsMissingWithNonArgumentParameterInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(IsMissingWithNonArgumentParameterInspection), CultureInfo.CurrentUICulture);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/LineLabelNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/LineLabelNotUsedInspection.cs
index d92513da55..8ad183f1d8 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/LineLabelNotUsedInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/LineLabelNotUsedInspection.cs
@@ -1,4 +1,3 @@
-using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.Parsing.Grammar;
@@ -6,6 +5,8 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -46,7 +47,7 @@ internal sealed class LineLabelNotUsedInspection : DeclarationInspectionBase
{
public LineLabelNotUsedInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.LineLabel)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -61,8 +62,8 @@ protected override string ResultDescription(Declaration declaration)
var declarationType = declaration.DeclarationType.ToLocalizedString();
var declarationName = declaration.IdentifierName;
return string.Format(
- InspectionResults.IdentifierNotUsedInspection,
- declarationType,
+ InspectionResults.ResourceManager.GetString(nameof(InspectionResults.IdentifierNotUsedInspection), CultureInfo.CurrentUICulture),
+ declarationType,
declarationName);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MemberNotOnInterfaceInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MemberNotOnInterfaceInspection.cs
index 2a28f1e885..7a94dd61a0 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MemberNotOnInterfaceInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MemberNotOnInterfaceInspection.cs
@@ -1,6 +1,4 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
@@ -8,6 +6,9 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -45,7 +46,7 @@ internal sealed class MemberNotOnInterfaceInspection : DeclarationInspectionBase
{
public MemberNotOnInterfaceInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override IEnumerable RelevantDeclarationsInModule(QualifiedModuleName module, DeclarationFinder finder)
{
@@ -94,7 +95,7 @@ protected override string ResultDescription(Declaration declaration, Declaration
var memberName = declaration.IdentifierName;
var typeName = typeDeclaration?.IdentifierName ?? string.Empty;
return string.Format(
- InspectionResults.MemberNotOnInterfaceInspection,
+ InspectionResults.ResourceManager.GetString(nameof(MemberNotOnInterfaceInspection), CultureInfo.CurrentUICulture),
memberName,
typeName);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MisleadingByRefParameterInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MisleadingByRefParameterInspection.cs
index 7b88433fc7..65d5691cfc 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MisleadingByRefParameterInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MisleadingByRefParameterInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
@@ -58,14 +59,14 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
&& parameter.IsByRef && !parameter.IsImplicitByRef;
}
- private static bool IsAlwaysByRef(Declaration parameter)
+ private static bool IsAlwaysByRef(Declaration parameter)
=> parameter.IsArray
|| (parameter.AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.UserDefinedType) ?? false);
protected override string ResultDescription(Declaration declaration)
{
return string.Format(
- InspectionResults.MisleadingByRefParameterInspection,
+ InspectionResults.ResourceManager.GetString(nameof(MisleadingByRefParameterInspection), CultureInfo.CurrentUICulture),
declaration.IdentifierName, declaration.ParentDeclaration.QualifiedName.MemberName);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs
index f6664a961d..ee8430598f 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs
@@ -1,5 +1,3 @@
-using System.Collections.Generic;
-using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Results;
using Rubberduck.Parsing;
@@ -9,6 +7,9 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -42,7 +43,7 @@ internal sealed class MissingAnnotationArgumentInspection : InspectionBase
{
public MissingAnnotationArgumentInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override IEnumerable DoGetInspectionResults(DeclarationFinder finder)
{
@@ -79,7 +80,7 @@ private IInspectionResult InspectionResult(IParseTreeAnnotation pta)
private static string ResultDescription(IParseTreeAnnotation pta)
{
return string.Format(
- InspectionResults.MissingAnnotationArgumentInspection,
+ InspectionResults.ResourceManager.GetString(nameof(MissingAnnotationArgumentInspection), CultureInfo.CurrentUICulture),
pta.Annotation.Name);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs
index 3e9bc58d5f..08758940b2 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs
@@ -1,5 +1,3 @@
-using System.Collections.Generic;
-using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Parsing.Annotations;
@@ -8,6 +6,9 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor.SafeComWrappers;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -44,7 +45,7 @@ internal sealed class MissingAttributeInspection : DeclarationInspectionMultiRes
{
public MissingAttributeInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override IEnumerable ResultProperties(Declaration declaration, DeclarationFinder finder)
{
@@ -60,8 +61,8 @@ protected override IEnumerable ResultProperties(Declaratio
}
protected override string ResultDescription(Declaration declaration, IParseTreeAnnotation pta) =>
- string.Format(InspectionResults.MissingAttributeInspection, declaration.IdentifierName, pta.Annotation.Name);
-
+ string.Format(InspectionResults.ResourceManager.GetString(nameof(MissingAttributeInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName, pta.Annotation.Name);
+
private static bool MissesCorrespondingAttribute(Declaration declaration, IParseTreeAnnotation annotationInstance)
{
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs
index 684d4bc447..58454e4e58 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs
@@ -1,12 +1,13 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor.SafeComWrappers;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -41,8 +42,8 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
internal sealed class MissingMemberAnnotationInspection : DeclarationInspectionMultiResultBase<(string AttributeName, IReadOnlyList AttriguteValues)>
{
public MissingMemberAnnotationInspection(IDeclarationFinderProvider declarationFinderProvider)
- : base(declarationFinderProvider, new DeclarationType[0], new []{DeclarationType.Module })
- {}
+ : base(declarationFinderProvider, new DeclarationType[0], new[] { DeclarationType.Module })
+ { }
protected override IEnumerable<(string AttributeName, IReadOnlyList AttriguteValues)> ResultProperties(Declaration declaration, DeclarationFinder finder)
{
@@ -68,10 +69,11 @@ private static bool MissesCorrespondingMemberAnnotation(Declaration declaration,
if (attributeBaseName == "VB_Ext_Key")
{
return !declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation)
- .Any(pta => {
- var annotation = (IAttributeAnnotation)pta.Annotation;
- return annotation.Attribute(pta).Equals("VB_Ext_Key") && attribute.Values[0].Equals(annotation.AttributeValues(pta)[0]);
- });
+ .Any(pta =>
+ {
+ var annotation = (IAttributeAnnotation)pta.Annotation;
+ return annotation.Attribute(pta).Equals("VB_Ext_Key") && attribute.Values[0].Equals(annotation.AttributeValues(pta)[0]);
+ });
}
return !declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation)
@@ -86,7 +88,7 @@ private static string AttributeBaseName(Declaration declaration, AttributeNode a
protected override string ResultDescription(Declaration declaration, (string AttributeName, IReadOnlyList AttriguteValues) properties)
{
var (attributeBaseName, attributeValues) = properties;
- return string.Format(InspectionResults.MissingMemberAnnotationInspection,
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(MissingMemberAnnotationInspection), CultureInfo.CurrentUICulture),
declaration.IdentifierName,
attributeBaseName,
string.Join(", ", attributeValues));
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs
index fbd8edbe72..743c497639 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs
@@ -1,11 +1,12 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -38,8 +39,8 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
internal sealed class MissingModuleAnnotationInspection : DeclarationInspectionMultiResultBase<(string AttributeName, IReadOnlyList AttributeValues)>
{
public MissingModuleAnnotationInspection(IDeclarationFinderProvider declarationFinderProvider)
- : base(declarationFinderProvider, new []{DeclarationType.Module}, new []{DeclarationType.Document})
- {}
+ : base(declarationFinderProvider, new[] { DeclarationType.Module }, new[] { DeclarationType.Document })
+ { }
protected override IEnumerable<(string AttributeName, IReadOnlyList AttributeValues)> ResultProperties(Declaration declaration, DeclarationFinder finder)
{
@@ -50,7 +51,7 @@ public MissingModuleAnnotationInspection(IDeclarationFinderProvider declarationF
private static bool IsResultAttribute(AttributeNode attribute, Declaration declaration)
{
- return !IsDefaultAttribute(declaration, attribute)
+ return !IsDefaultAttribute(declaration, attribute)
&& MissesCorrespondingModuleAnnotation(declaration, attribute);
}
@@ -74,7 +75,8 @@ private static bool MissesCorrespondingModuleAnnotation(Declaration declaration,
if (attribute.Name == "VB_Ext_Key")
{
return !declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation)
- .Any(pta => {
+ .Any(pta =>
+ {
var annotation = (IAttributeAnnotation)pta.Annotation;
return annotation.Attribute(pta).Equals("VB_Ext_Key") && attribute.Values[0].Equals(annotation.AttributeValues(pta)[0]);
});
@@ -86,7 +88,7 @@ private static bool MissesCorrespondingModuleAnnotation(Declaration declaration,
protected override string ResultDescription(Declaration declaration, (string AttributeName, IReadOnlyList AttributeValues) properties)
{
- return string.Format(InspectionResults.MissingMemberAnnotationInspection,
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(MissingMemberAnnotationInspection), CultureInfo.CurrentUICulture),
declaration.IdentifierName,
properties.AttributeName,
string.Join(", ", properties.AttributeValues));
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleScopeDimKeywordInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleScopeDimKeywordInspection.cs
index c649215252..0608d2bcc2 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleScopeDimKeywordInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleScopeDimKeywordInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -46,7 +47,7 @@ protected override string ResultDescription(QualifiedContext !reference.ParentScoping.Equals(usageMember)))
{
return false;
@@ -89,7 +90,7 @@ private static bool IsRubberduckAssertField(Declaration fieldDeclaration)
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.MoveFieldCloserToUsageInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(MoveFieldCloserToUsageInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MultilineParameterInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MultilineParameterInspection.cs
index dd384592e3..8697b84f6b 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MultilineParameterInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MultilineParameterInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -39,7 +40,7 @@ public MultilineParameterInspection(IDeclarationFinderProvider declarationFinder
{
ContextListener = new ParameterListener();
}
-
+
protected override IInspectionListener ContextListener { get; }
protected override string ResultDescription(QualifiedContext context)
@@ -47,8 +48,8 @@ protected override string ResultDescription(QualifiedContext 3
- ? CodeAnalysisUI.EasterEgg_Continuator
- : Resources.Inspections.InspectionResults.MultilineParameterInspection,
+ ? CodeAnalysisUI.ResourceManager.GetString(nameof(CodeAnalysisUI.EasterEgg_Continuator), CultureInfo.CurrentUICulture)
+ : Resources.Inspections.InspectionResults.ResourceManager.GetString(nameof(MultilineParameterInspection), CultureInfo.CurrentUICulture),
parameterText);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MultipleDeclarationsInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MultipleDeclarationsInspection.cs
index ca975181e1..20eeab1748 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MultipleDeclarationsInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MultipleDeclarationsInspection.cs
@@ -5,6 +5,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -50,7 +51,7 @@ public MultipleDeclarationsInspection(IDeclarationFinderProvider declarationFind
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.MultipleDeclarationsInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(MultipleDeclarationsInspection), CultureInfo.CurrentUICulture);
}
private class ParameterListListener : InspectionListenerBase
@@ -59,7 +60,7 @@ public override void ExitVariableListStmt([NotNull] VBAParser.VariableListStmtCo
{
if (context.variableSubStmt().Length > 1)
{
- SaveContext(context);
+ SaveContext(context);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/NonReturningFunctionInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/NonReturningFunctionInspection.cs
index e496396a09..f73cb5413b 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/NonReturningFunctionInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/NonReturningFunctionInspection.cs
@@ -1,4 +1,3 @@
-using System.Linq;
using Antlr4.Runtime.Tree;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
@@ -7,6 +6,8 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -42,7 +43,7 @@ internal sealed class NonReturningFunctionInspection : DeclarationInspectionBase
{
public NonReturningFunctionInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Function)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -59,7 +60,7 @@ private bool IsAssigned(Declaration member, DeclarationFinder finder)
var inScopeIdentifierReferences = member.References
.Where(reference => reference.ParentScoping.Equals(member));
return inScopeIdentifierReferences
- .Any(reference => reference.IsAssignment
+ .Any(reference => reference.IsAssignment
|| IsAssignedByRefArgument(member, reference, finder));
}
@@ -97,7 +98,7 @@ private static VBAParser.ArgumentExpressionContext ImmediateArgumentExpressionCo
private static bool IsReturningUserDefinedType(Declaration member)
{
- return member.AsTypeDeclaration != null
+ return member.AsTypeDeclaration != null
&& member.AsTypeDeclaration.DeclarationType == DeclarationType.UserDefinedType;
}
@@ -114,7 +115,7 @@ private static bool IsUserDefinedTypeAssigned(Declaration member)
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.NonReturningFunctionInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(NonReturningFunctionInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
///
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectVariableNotSetInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectVariableNotSetInspection.cs
index 2a8457f0d8..836f4c3ce1 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectVariableNotSetInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectVariableNotSetInspection.cs
@@ -1,7 +1,4 @@
-using System;
-using System.Collections.Generic;
-using System.Linq;
-using Antlr4.Runtime;
+using Antlr4.Runtime;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
@@ -10,6 +7,10 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -46,7 +47,7 @@ internal sealed class ObjectVariableNotSetInspection : IdentifierReferenceInspec
{
public ObjectVariableNotSetInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override IEnumerable ReferencesInModule(QualifiedModuleName module, DeclarationFinder finder)
{
@@ -89,7 +90,7 @@ private static IEnumerable PossiblyObjectNonSetAssignments(
var assignments = finder.IdentifierReferences(module)
.Where(reference => reference.IsAssignment
&& !reference.IsSetAssignment
- && (reference.IsNonIndexedDefaultMemberAccess
+ && (reference.IsNonIndexedDefaultMemberAccess
|| Tokens.Variant.Equals(reference.Declaration.AsTypeName, StringComparison.InvariantCultureIgnoreCase)));
var unboundAssignments = finder.UnboundDefaultMemberAccesses(module)
.Where(reference => reference.IsAssignment);
@@ -104,7 +105,7 @@ protected override bool IsResultReference(IdentifierReference reference, Declara
protected override string ResultDescription(IdentifierReference reference)
{
- return string.Format(InspectionResults.ObjectVariableNotSetInspection, reference.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ObjectVariableNotSetInspection), CultureInfo.CurrentUICulture), reference.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectWhereProcedureIsRequiredInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectWhereProcedureIsRequiredInspection.cs
index bad877aef6..e61f1ce89e 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectWhereProcedureIsRequiredInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectWhereProcedureIsRequiredInspection.cs
@@ -1,12 +1,13 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Results;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -101,7 +102,7 @@ private static string BoundResultDescription(IdentifierReference reference)
{
var expression = reference.IdentifierName;
var defaultMember = reference.Declaration.QualifiedName.ToString();
- return string.Format(InspectionResults.ObjectWhereProcedureIsRequiredInspection, expression, defaultMember);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ObjectWhereProcedureIsRequiredInspection), CultureInfo.CurrentUICulture), expression, defaultMember);
}
private IEnumerable UnboundInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
@@ -117,7 +118,7 @@ private IEnumerable UnboundInspectionResults(QualifiedModuleN
private IInspectionResult UnboundInspectionResult(IdentifierReference reference, DeclarationFinder finder)
{
- var disabledQuickFixes = new List{ "ExpandDefaultMemberQuickFix" };
+ var disabledQuickFixes = new List { "ExpandDefaultMemberQuickFix" };
return new IdentifierReferenceInspectionResult(
this,
UnboundResultDescription(reference),
@@ -129,7 +130,7 @@ private IInspectionResult UnboundInspectionResult(IdentifierReference reference,
private static string UnboundResultDescription(IdentifierReference reference)
{
var expression = reference.IdentifierName;
- return string.Format(InspectionResults.ObjectWhereProcedureIsRequiredInspection_Unbound, expression);
+ return string.Format(InspectionResults.ResourceManager.GetString("ObjectWhereProcedureIsRequiredInspection_Unbound", CultureInfo.CurrentUICulture), expression);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallStatementInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallStatementInspection.cs
index 55fbfb6f49..98fca0e223 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallStatementInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallStatementInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -51,7 +52,7 @@ public ObsoleteCallStatementInspection(IDeclarationFinderProvider declarationFin
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.ObsoleteCallStatementInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(ObsoleteCallStatementInspection), CultureInfo.CurrentUICulture);
}
protected override bool IsResultContext(QualifiedContext context, DeclarationFinder finder)
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallingConventionInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallingConventionInspection.cs
index 923df5ec31..a28360cc22 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallingConventionInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCallingConventionInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -40,9 +41,9 @@ public ObsoleteCallingConventionInspection(IDeclarationFinderProvider declaratio
protected override string ResultDescription(QualifiedContext context)
{
- var identifierName = ((VBAParser.DeclareStmtContext) context.Context).identifier().GetText();
+ var identifierName = ((VBAParser.DeclareStmtContext)context.Context).identifier().GetText();
return string.Format(
- InspectionResults.ObsoleteCallingConventionInspection,
+ InspectionResults.ResourceManager.GetString(nameof(ObsoleteCallingConventionInspection), CultureInfo.CurrentUICulture),
identifierName);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCommentSyntaxInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCommentSyntaxInspection.cs
index 3b7fc0af7a..8d80471076 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCommentSyntaxInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteCommentSyntaxInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -42,7 +43,7 @@ public ObsoleteCommentSyntaxInspection(IDeclarationFinderProvider declarationFin
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.ObsoleteCommentSyntaxInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(ObsoleteCommentSyntaxInspection), CultureInfo.CurrentUICulture);
}
private class ObsoleteCommentSyntaxListener : InspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteErrorSyntaxInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteErrorSyntaxInspection.cs
index 73615bb07c..32cbeb25e3 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteErrorSyntaxInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteErrorSyntaxInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -42,7 +43,7 @@ public ObsoleteErrorSyntaxInspection(IDeclarationFinderProvider declarationFinde
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.ObsoleteErrorSyntaxInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(ObsoleteErrorSyntaxInspection), CultureInfo.CurrentUICulture);
}
private class ObsoleteErrorSyntaxListener : InspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteGlobalInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteGlobalInspection.cs
index 72fdc31898..b6ddfd2a49 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteGlobalInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteGlobalInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -33,11 +34,11 @@ internal sealed class ObsoleteGlobalInspection : DeclarationInspectionBase
{
public ObsoleteGlobalInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
- return declaration.Accessibility == Accessibility.Global
+ return declaration.Accessibility == Accessibility.Global
&& declaration.Context != null
&& declaration.DeclarationType != DeclarationType.BracketedExpression;
}
@@ -47,7 +48,7 @@ protected override string ResultDescription(Declaration declaration)
var declarationType = declaration.DeclarationType.ToLocalizedString();
var declarationName = declaration.IdentifierName;
return string.Format(
- InspectionResults.ObsoleteGlobalInspection,
+ InspectionResults.ResourceManager.GetString(nameof(ObsoleteGlobalInspection), CultureInfo.CurrentUICulture),
declarationType,
declarationName);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteLetStatementInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteLetStatementInspection.cs
index 249556a1fc..c23c0a04ac 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteLetStatementInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteLetStatementInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -39,12 +40,12 @@ public ObsoleteLetStatementInspection(IDeclarationFinderProvider declarationFind
{
ContextListener = new ObsoleteLetStatementListener();
}
-
+
protected override IInspectionListener ContextListener { get; }
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.ObsoleteLetStatementInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(ObsoleteLetStatementInspection), CultureInfo.CurrentUICulture);
}
private class ObsoleteLetStatementListener : InspectionListenerBase
@@ -53,7 +54,7 @@ public override void ExitLetStmt(VBAParser.LetStmtContext context)
{
if (context.LET() != null)
{
- SaveContext(context);
+ SaveContext(context);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs
index 340f529e8a..01a8bdf5be 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs
@@ -1,10 +1,11 @@
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -54,7 +55,7 @@ internal sealed class ObsoleteMemberUsageInspection : IdentifierReferenceInspect
{
public ObsoleteMemberUsageInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
{
@@ -72,7 +73,7 @@ protected override string ResultDescription(IdentifierReference reference)
.AnnotationArguments
.FirstOrDefault() ?? string.Empty;
return string.Format(
- InspectionResults.ObsoleteMemberUsageInspection,
+ InspectionResults.ResourceManager.GetString(nameof(ObsoleteMemberUsageInspection), CultureInfo.CurrentUICulture),
reference.IdentifierName,
replacementDocumentation);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteTypeHintInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteTypeHintInspection.cs
index cfc5898a90..b6b5c68236 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteTypeHintInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteTypeHintInspection.cs
@@ -1,12 +1,14 @@
-using System.Collections.Generic;
-using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.CodeAnalysis.Inspections.Results;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -40,7 +42,7 @@ internal sealed class ObsoleteTypeHintInspection : InspectionBase
{
public ObsoleteTypeHintInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override IEnumerable DoGetInspectionResults(DeclarationFinder finder)
{
@@ -74,11 +76,11 @@ private IInspectionResult InspectionResult(Declaration declaration)
private static string ResultDescription(Declaration declaration)
{
- var declarationTypeName = declaration.DeclarationType.ToString().ToLower();
+ var declarationTypeName = declaration.DeclarationType.ToLocalizedString();
var identifierName = declaration.IdentifierName;
return string.Format(
- InspectionResults.ObsoleteTypeHintInspection,
- InspectionsUI.Inspections_Declaration,
+ InspectionResults.ResourceManager.GetString("ObsoleteTypeHintInspection", CultureInfo.CurrentUICulture),
+ InspectionsUI.ResourceManager.GetString("Inspections_Declaration", CultureInfo.CurrentUICulture),
declarationTypeName,
identifierName);
}
@@ -104,10 +106,10 @@ private IInspectionResult InspectionResult(IdentifierReference reference, Declar
private string ResultDescription(IdentifierReference reference)
{
- var declarationTypeName = reference.Declaration.DeclarationType.ToString().ToLower();
+ var declarationTypeName = reference.Declaration.DeclarationType.ToLocalizedString();
var identifierName = reference.IdentifierName;
- return string.Format(InspectionResults.ObsoleteTypeHintInspection,
- InspectionsUI.Inspections_Usage,
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ObsoleteTypeHintInspection), CultureInfo.CurrentUICulture),
+ InspectionsUI.ResourceManager.GetString(nameof(InspectionsUI.Inspections_Usage), CultureInfo.CurrentUICulture),
declarationTypeName,
identifierName);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteWhileWendStatementInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteWhileWendStatementInspection.cs
index 93f1623154..98259d2c75 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteWhileWendStatementInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteWhileWendStatementInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -47,7 +48,7 @@ public ObsoleteWhileWendStatementInspection(IDeclarationFinderProvider declarati
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.ObsoleteWhileWendStatementInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(ObsoleteWhileWendStatementInspection), CultureInfo.CurrentUICulture);
}
private class ObsoleteWhileWendStatementListener : InspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/OnLocalErrorInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/OnLocalErrorInspection.cs
index 3b7b0a371b..45a79af915 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/OnLocalErrorInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/OnLocalErrorInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -51,7 +52,7 @@ public OnLocalErrorInspection(IDeclarationFinderProvider declarationFinderProvid
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.OnLocalErrorInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(OnLocalErrorInspection), CultureInfo.CurrentUICulture);
}
private class OnLocalErrorListener : InspectionListenerBase
@@ -60,7 +61,7 @@ public override void ExitOnErrorStmt([NotNull] VBAParser.OnErrorStmtContext cont
{
if (context.ON_LOCAL_ERROR() != null)
{
- SaveContext(context);
+ SaveContext(context);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionBaseInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionBaseInspection.cs
index cc4c9dd966..d9f360bc2f 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionBaseInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionBaseInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -46,14 +47,14 @@ public OptionBaseInspection(IDeclarationFinderProvider declarationFinderProvider
{
ContextListener = new OptionBaseStatementListener();
}
-
+
protected override IInspectionListener ContextListener { get; }
protected override string ResultDescription(QualifiedContext context)
{
var moduleName = context.ModuleName.ComponentName;
return string.Format(
- InspectionResults.OptionBaseInspection,
+ InspectionResults.ResourceManager.GetString(nameof(OptionBaseInspection), CultureInfo.CurrentUICulture),
moduleName);
}
@@ -63,7 +64,7 @@ public override void ExitOptionBaseStmt(VBAParser.OptionBaseStmtContext context)
{
if (context.numberLiteral()?.INTEGERLITERAL().Symbol.Text == "1")
{
- SaveContext(context);
+ SaveContext(context);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionExplicitInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionExplicitInspection.cs
index 175cc0f6f8..34f43a7db0 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionExplicitInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/OptionExplicitInspection.cs
@@ -1,4 +1,3 @@
-using System.Collections.Generic;
using Antlr4.Runtime.Misc;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
@@ -7,6 +6,8 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -47,7 +48,7 @@ public OptionExplicitInspection(IDeclarationFinderProvider declarationFinderProv
ContextListener = new MissingOptionExplicitListener();
}
- protected override IInspectionListener ContextListener { get; }
+ protected override IInspectionListener ContextListener { get; }
protected override bool IsResultContext(QualifiedContext context, DeclarationFinder finder)
{
@@ -59,7 +60,7 @@ protected override string ResultDescription(QualifiedContext ParameterAtIndexIsNotUsed(implementation, parameterIndex));
}
@@ -136,13 +137,13 @@ private static bool ThereAreHandlersAndNoneUsesTheParameter(ParameterDeclaration
var handlers = finder.FindEventHandlers(eventDeclaration).ToList();
//We do not want to report all parameters of not handled events.
- return handlers.Any()
+ return handlers.Any()
&& handlers.All(handler => ParameterAtIndexIsNotUsed(handler, parameterIndex));
}
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.ParameterNotUsedInspection, declaration.IdentifierName).Capitalize();
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ParameterNotUsedInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName).Capitalize();
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterlessCellsInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterlessCellsInspection.cs
new file mode 100644
index 0000000000..a0da3ac9ad
--- /dev/null
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterlessCellsInspection.cs
@@ -0,0 +1,93 @@
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Attributes;
+using Rubberduck.Parsing;
+using Rubberduck.Parsing.Grammar;
+using Rubberduck.Parsing.Symbols;
+using Rubberduck.Parsing.VBA;
+using Rubberduck.Parsing.VBA.DeclarationCaching;
+using Rubberduck.Resources.Inspections;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
+
+namespace Rubberduck.CodeAnalysis.Inspections.Concrete
+{
+ ///
+ /// Identifies parameterless 'Range.Cells' member calls.
+ ///
+ ///
+ ///
+ /// Range.Cells is a parameterized Property Get procedure that accepts RowIndex and ColumnIndex parameters, both optional
+ /// to avoid requiring either when only one needs to be supplied. If no parameters are provided,
+ /// Cells simply returns a reference to the parent Range object, making a parameterless call entirely redundant.
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ [RequiredLibrary("Excel")]
+ internal sealed class ParameterlessCellsInspection : IdentifierReferenceInspectionBase
+ {
+ public ParameterlessCellsInspection(IDeclarationFinderProvider declarationFinderProvider)
+ : base(declarationFinderProvider)
+ {
+ }
+
+ protected override IEnumerable DoGetInspectionResults(DeclarationFinder finder)
+ {
+ var excel = finder.Projects.SingleOrDefault(item => !item.IsUserDefined && item.IdentifierName == "Excel");
+ if (excel is null)
+ {
+ yield break;
+ }
+
+ var range = finder.Classes.SingleOrDefault(item => !item.IsUserDefined && item.IdentifierName == "Range" && item.ProjectId == excel.ProjectId);
+ if (range is null)
+ {
+ yield break;
+ }
+
+ var cells = finder.Members(range).SingleOrDefault(item => item.IdentifierName == "Cells" && item.DeclarationType == DeclarationType.PropertyGet);
+ if (cells is null)
+ {
+ yield break;
+ }
+
+ foreach (var reference in cells.References.Where(reference => IsResultReference(reference, finder)))
+ {
+ yield return InspectionResult(reference, finder);
+ }
+ }
+
+ protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
+ {
+ var memberAccess = reference.Context.GetAncestor();
+ var memberArgs = memberAccess?.GetAncestor()?.argumentList();
+
+ return memberAccess != null && !memberArgs.GetDescendents().Any();
+ }
+
+ protected override string ResultDescription(IdentifierReference reference)
+ {
+ return InspectionResults.ResourceManager.GetString(nameof(ParameterlessCellsInspection), CultureInfo.CurrentUICulture);
+ }
+ }
+}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs
index 24ebd6735d..e59aadfd5d 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs
@@ -1,11 +1,12 @@
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -53,8 +54,8 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
internal sealed class ProcedureCanBeWrittenAsFunctionInspection : DeclarationInspectionBase
{
public ProcedureCanBeWrittenAsFunctionInspection(IDeclarationFinderProvider declarationFinderProvider)
- : base(declarationFinderProvider, new []{DeclarationType.Procedure}, new []{DeclarationType.LibraryProcedure, DeclarationType.PropertyLet, DeclarationType.PropertySet})
- {}
+ : base(declarationFinderProvider, new[] { DeclarationType.Procedure }, new[] { DeclarationType.LibraryProcedure, DeclarationType.PropertyLet, DeclarationType.PropertySet })
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -119,7 +120,7 @@ private static VBAParser.ArgumentExpressionContext ImmediateArgumentExpressionCo
protected override string ResultDescription(Declaration declaration)
{
return string.Format(
- InspectionResults.ProcedureCanBeWrittenAsFunctionInspection,
+ InspectionResults.ResourceManager.GetString(nameof(ProcedureCanBeWrittenAsFunctionInspection), CultureInfo.CurrentUICulture),
declaration.IdentifierName);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureNotUsedInspection.cs
index 14a795906c..59ca3e4b5d 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureNotUsedInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureNotUsedInspection.cs
@@ -1,5 +1,3 @@
-using System.Collections.Generic;
-using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.Parsing.Annotations;
@@ -8,6 +6,8 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -110,7 +110,7 @@ internal sealed class ProcedureNotUsedInspection : DeclarationInspectionBase
{
public ProcedureNotUsedInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, ProcedureTypes)
- {}
+ { }
private static readonly DeclarationType[] ProcedureTypes =
{
@@ -143,10 +143,10 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
.Any(reference => !reference.ParentScoping.Equals(declaration)) // ignore recursive/self-referential calls
&& !finder.FindEventHandlers().Contains(declaration)
&& !IsClassLifeCycleHandler(declaration)
- && !(declaration is ModuleBodyElementDeclaration member
+ && !(declaration is ModuleBodyElementDeclaration member
&& member.IsInterfaceImplementation)
&& !declaration.Annotations
- .Any(pta => pta.Annotation is ITestAnnotation)
+ .Any(pta => pta.Annotation is ITestAnnotation)
&& !IsDocumentEventHandler(declaration)
&& !IsEntryPoint(declaration)
&& !IsPublicInExposedClass(declaration);
@@ -154,13 +154,13 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
private static bool IsPublicInExposedClass(Declaration procedure)
{
- if(!(procedure.Accessibility == Accessibility.Public
+ if (!(procedure.Accessibility == Accessibility.Public
|| procedure.Accessibility == Accessibility.Global))
{
return false;
}
- if(!(Declaration.GetModuleParent(procedure) is ClassModuleDeclaration classParent))
+ if (!(Declaration.GetModuleParent(procedure) is ClassModuleDeclaration classParent))
{
return false;
}
@@ -168,7 +168,7 @@ private static bool IsPublicInExposedClass(Declaration procedure)
return classParent.IsExposed;
}
- private static bool IsEntryPoint(Declaration procedure) =>
+ private static bool IsEntryPoint(Declaration procedure) =>
procedure.Annotations.Any(pta => pta.Annotation is EntryPointAnnotation || pta.Annotation is ExcelHotKeyAnnotation);
private static bool IsClassLifeCycleHandler(Declaration procedure)
@@ -179,7 +179,7 @@ private static bool IsClassLifeCycleHandler(Declaration procedure)
}
var parent = Declaration.GetModuleParent(procedure);
- return parent != null
+ return parent != null
&& parent.DeclarationType.HasFlag(DeclarationType.ClassModule);
}
@@ -195,8 +195,8 @@ protected override string ResultDescription(Declaration declaration)
var declarationType = declaration.DeclarationType.ToLocalizedString();
var declarationName = declaration.IdentifierName;
return string.Format(
- InspectionResults.IdentifierNotUsedInspection,
- declarationType,
+ InspectionResults.ResourceManager.GetString(nameof(InspectionResults.IdentifierNotUsedInspection), CultureInfo.CurrentUICulture),
+ declarationType,
declarationName);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureRequiredInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureRequiredInspection.cs
index 3566070fad..db1632b6c4 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureRequiredInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureRequiredInspection.cs
@@ -1,10 +1,11 @@
-using System.Collections.Generic;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -74,7 +75,7 @@ protected override string ResultDescription(IdentifierReference failedCoercion)
{
var expression = failedCoercion.IdentifierName;
var typeName = failedCoercion.Declaration?.FullAsTypeName;
- return string.Format(InspectionResults.ProcedureRequiredInspection, expression, typeName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ProcedureRequiredInspection), CultureInfo.CurrentUICulture), expression, typeName);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/PublicControlFieldAccessInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/PublicControlFieldAccessInspection.cs
index 9f2f983c32..3ee7ce0b52 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/PublicControlFieldAccessInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/PublicControlFieldAccessInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -156,7 +157,7 @@ protected override bool IsResultReference(IdentifierReference reference, Declara
protected override string ResultDescription(IdentifierReference reference)
{
- return string.Format(InspectionResults.PublicControlFieldAccessInspection, reference.Declaration.ParentDeclaration.IdentifierName, reference.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(PublicControlFieldAccessInspection), CultureInfo.CurrentUICulture), reference.Declaration.ParentDeclaration.IdentifierName, reference.IdentifierName);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/PublicEnumerationDeclaredInWorksheetInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/PublicEnumerationDeclaredInWorksheetInspection.cs
index ac5bbe60e4..24fb37be0f 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/PublicEnumerationDeclaredInWorksheetInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/PublicEnumerationDeclaredInWorksheetInspection.cs
@@ -6,6 +6,7 @@
using Rubberduck.VBEditor.SafeComWrappers;
using System;
using System.Collections.Generic;
+using System.Globalization;
using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
@@ -44,7 +45,7 @@ internal sealed class PublicEnumerationDeclaredInWorksheetInspection : Declarati
public PublicEnumerationDeclaredInWorksheetInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Enumeration)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration enumeration, DeclarationFinder finder)
{
@@ -62,8 +63,7 @@ protected override bool IsResultDeclaration(Declaration enumeration, Declaration
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.PublicEnumerationDeclaredInWorksheetInspection,
- declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(PublicEnumerationDeclaredInWorksheetInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
///
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/PublicImplementationShouldBePrivateInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/PublicImplementationShouldBePrivateInspection.cs
index 69e5166b39..d67dbb314f 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/PublicImplementationShouldBePrivateInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/PublicImplementationShouldBePrivateInspection.cs
@@ -1,16 +1,12 @@
-using Rubberduck.CodeAnalysis.CodeMetrics;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Refactorings.Common;
-using Rubberduck.Resources.Inspections;
-using Rubberduck.VBEditor;
using System;
using System.Collections.Generic;
+using System.Globalization;
using System.Linq;
-using System.Text;
-using System.Threading.Tasks;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -78,7 +74,7 @@ internal sealed class PublicImplementationShouldBePrivateInspection : Declaratio
{
public PublicImplementationShouldBePrivateInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Member)
- {}
+ { }
//Overriding DoGetInspectionResults in order to dereference the DeclarationFinder FindXXX declaration
//lists only once per inspections pass.
@@ -109,11 +105,11 @@ protected override IEnumerable DoGetInspectionResults(Declara
private static IEnumerable FindDocumentEventHandlers(IEnumerable publicMembers)
{
//Excel and Word
- var docEventPrefixes = new List()
- {
- "Workbook",
- "Worksheet",
- "Document"
+ var docEventPrefixes = new List()
+ {
+ "Workbook",
+ "Worksheet",
+ "Document"
};
//FindDocumentEventHandlers can be a source of False Positives if a Document's code
@@ -125,7 +121,7 @@ private static IEnumerable FindDocumentEventHandlers(IEnumerable 2 //Excel and Word document events all have at least 3 characters
&& !splitup[1].Any(c => char.IsDigit(c)); //Excel and Word document event names do not contain numbers
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ReadOnlyPropertyAssignmentInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ReadOnlyPropertyAssignmentInspection.cs
index 65ad96bb73..f88af4e98f 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ReadOnlyPropertyAssignmentInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ReadOnlyPropertyAssignmentInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
@@ -129,7 +130,7 @@ protected override string ResultDescription(IdentifierReference reference)
{
var identifierName = reference.IdentifierName;
return string.Format(
- InspectionResults.ReadOnlyPropertyAssignmentInspection, identifierName);
+ InspectionResults.ResourceManager.GetString(nameof(ReadOnlyPropertyAssignmentInspection), CultureInfo.CurrentUICulture), identifierName);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantByRefModifierInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantByRefModifierInspection.cs
index 875577f770..18c8600f4c 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantByRefModifierInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantByRefModifierInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -40,7 +41,7 @@ internal sealed class RedundantByRefModifierInspection : DeclarationInspectionBa
{
public RedundantByRefModifierInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Parameter)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -66,9 +67,7 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(
- InspectionResults.RedundantByRefModifierInspection,
- declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(RedundantByRefModifierInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantOptionInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantOptionInspection.cs
index dc59e8e2b5..474d3e9a44 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantOptionInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/RedundantOptionInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -48,9 +49,7 @@ public RedundantOptionInspection(IDeclarationFinderProvider declarationFinderPro
protected override string ResultDescription(QualifiedContext context)
{
- return string.Format(
- InspectionResults.RedundantOptionInspection,
- context.Context.GetText());
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(RedundantOptionInspection), CultureInfo.CurrentUICulture), context.Context.GetText());
}
private class RedundantModuleOptionListener : InspectionListenerBase
@@ -59,7 +58,7 @@ public override void ExitOptionBaseStmt(VBAParser.OptionBaseStmtContext context)
{
if (context.numberLiteral()?.INTEGERLITERAL().Symbol.Text == "0")
{
- SaveContext(context);
+ SaveContext(context);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/SelfAssignedDeclarationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/SelfAssignedDeclarationInspection.cs
index 2d7a3c37f9..2d68276d44 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/SelfAssignedDeclarationInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/SelfAssignedDeclarationInspection.cs
@@ -1,10 +1,11 @@
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -48,7 +49,7 @@ internal sealed class SelfAssignedDeclarationInspection : DeclarationInspectionB
{
public SelfAssignedDeclarationInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Variable)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -63,7 +64,7 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.SelfAssignedDeclarationInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(SelfAssignedDeclarationInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/SetAssignmentWithIncompatibleObjectTypeInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/SetAssignmentWithIncompatibleObjectTypeInspection.cs
index 57208eb6b5..c4d864c0bb 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/SetAssignmentWithIncompatibleObjectTypeInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/SetAssignmentWithIncompatibleObjectTypeInspection.cs
@@ -1,5 +1,4 @@
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
@@ -8,6 +7,8 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -93,7 +94,7 @@ protected override (bool isResult, string properties) IsResultReferenceWithAddit
var assignedTypeName = AssignedTypeName(reference, finder);
- if(assignedTypeName == null || SetAssignmentPossiblyLegal(reference.Declaration, assignedTypeName))
+ if (assignedTypeName == null || SetAssignmentPossiblyLegal(reference.Declaration, assignedTypeName))
{
return (false, null);
}
@@ -109,7 +110,7 @@ private static bool ToBeConsidered(IdentifierReference reference)
}
var declaration = reference.Declaration;
- return declaration?.AsTypeDeclaration != null
+ return declaration?.AsTypeDeclaration != null
&& declaration.IsObject;
}
@@ -165,7 +166,7 @@ protected override string ResultDescription(IdentifierReference reference, strin
{
var declarationName = reference.Declaration.IdentifierName;
var variableTypeName = reference.Declaration.FullAsTypeName;
- return string.Format(InspectionResults.SetAssignmentWithIncompatibleObjectTypeInspection, declarationName, variableTypeName, assignedTypeName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(SetAssignmentWithIncompatibleObjectTypeInspection), CultureInfo.CurrentUICulture), declarationName, variableTypeName, assignedTypeName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ShadowedDeclarationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ShadowedDeclarationInspection.cs
index cd093dc744..5d3ffe9c6d 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ShadowedDeclarationInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ShadowedDeclarationInspection.cs
@@ -1,7 +1,4 @@
-using System;
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.InternalApi.Extensions;
using Rubberduck.Parsing.Symbols;
@@ -9,6 +6,10 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.VBEditor;
using Rubberduck.VBEditor.SafeComWrappers;
+using System;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -55,13 +56,13 @@ private enum DeclarationSite
public ShadowedDeclarationInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override IDictionary> GlobalInformation(DeclarationFinder finder)
{
- return finder.UserDeclarations(DeclarationType.Project)
- .OfType()
- .ToDictionary(project => project.ProjectId, ReferencedProjectIds);
+ return finder.UserDeclarations(DeclarationType.Project)
+ .OfType()
+ .ToDictionary(project => project.ProjectId, ReferencedProjectIds);
}
protected override IDictionary> GlobalInformation(QualifiedModuleName module, DeclarationFinder finder)
@@ -92,7 +93,7 @@ protected override (bool isResult, Declaration properties) IsResultDeclarationWi
return (false, null);
}
- if(!referencedProjectIdsByProjectId.TryGetValue(userDeclaration.ProjectId, out var referencedProjectIds))
+ if (!referencedProjectIdsByProjectId.TryGetValue(userDeclaration.ProjectId, out var referencedProjectIds))
{
referencedProjectIds = new HashSet();
}
@@ -129,8 +130,8 @@ private static DeclarationSite GetDeclarationSite(Declaration originalDeclaratio
{
if (originalDeclaration.ProjectId != userDeclaration.ProjectId)
{
- return referencedProjectIds.Contains(originalDeclaration.ProjectId)
- ? DeclarationSite.ReferencedProject
+ return referencedProjectIds.Contains(originalDeclaration.ProjectId)
+ ? DeclarationSite.ReferencedProject
: DeclarationSite.NotApplicable;
}
@@ -342,20 +343,20 @@ private static bool DeclarationInTheSameComponentCanBeShadowed(Declaration origi
{
return DeclarationIsLocal(userDeclaration);
}
-
+
// Shadowing between two enumerations or enumeration members is not possible inside one component.
- if (((originalDeclaration.DeclarationType == DeclarationType.Enumeration
+ if (((originalDeclaration.DeclarationType == DeclarationType.Enumeration
&& userDeclaration.DeclarationType == DeclarationType.EnumerationMember)
|| (originalDeclaration.DeclarationType == DeclarationType.EnumerationMember
&& userDeclaration.DeclarationType == DeclarationType.Enumeration)))
- {
- var originalDeclarationIndex = originalDeclaration.Context.start.StartIndex;
- var userDeclarationIndex = userDeclaration.Context.start.StartIndex;
+ {
+ var originalDeclarationIndex = originalDeclaration.Context.start.StartIndex;
+ var userDeclarationIndex = userDeclaration.Context.start.StartIndex;
- // First declaration wins
- return originalDeclarationIndex > userDeclarationIndex
- // Enumeration member can have the same name as enclosing enumeration
- && !userDeclaration.Equals(originalDeclaration.ParentDeclaration);
+ // First declaration wins
+ return originalDeclarationIndex > userDeclarationIndex
+ // Enumeration member can have the same name as enclosing enumeration
+ && !userDeclaration.Equals(originalDeclaration.ParentDeclaration);
}
// Events don't have a body, so their parameters can't be accessed
@@ -364,7 +365,7 @@ private static bool DeclarationInTheSameComponentCanBeShadowed(Declaration origi
return false;
}
- return SameComponentTypeShadowingRelations[originalDeclaration.DeclarationType].Contains(userDeclaration.DeclarationType);
+ return SameComponentTypeShadowingRelations[originalDeclaration.DeclarationType].Contains(userDeclaration.DeclarationType);
}
private static bool DeclarationAccessibilityCanBeShadowed(Declaration originalDeclaration)
@@ -652,7 +653,7 @@ protected override string ResultDescription(Declaration declaration, Declaration
var shadowedDeclarationType = shadowedDeclaration.DeclarationType.ToLocalizedString();
var shadowedDeclarationName = shadowedDeclaration.QualifiedName.ToString();
return string.Format(
- Resources.Inspections.InspectionResults.ShadowedDeclarationInspection,
+ Resources.Inspections.InspectionResults.ResourceManager.GetString(nameof(ShadowedDeclarationInspection), CultureInfo.CurrentUICulture),
declarationType,
declarationName,
shadowedDeclarationType,
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs
index a1e98f2cfa..7a488380cd 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs
@@ -1,6 +1,4 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Common;
using Rubberduck.Parsing;
@@ -12,6 +10,9 @@
using Rubberduck.VBEditor.ComManagement;
using Rubberduck.VBEditor.SafeComWrappers;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -128,15 +129,15 @@ protected override (bool isResult, string properties) IsResultReferenceWithAddit
var hostWorkbookDeclaration = GetHostWorkbookDeclaration(finder);
- var context = reference.Context as VBAParser.MemberAccessExprContext
+ var context = reference.Context as VBAParser.MemberAccessExprContext
?? reference.Context.Parent as VBAParser.MemberAccessExprContext
?? reference.Context.Parent.Parent as VBAParser.MemberAccessExprContext;
if (context is VBAParser.MemberAccessExprContext memberAccess)
{
var appObjectDeclaration = GetHostApplicationDeclaration(finder);
- var isApplicationQualifier = appObjectDeclaration.References.Any(appRef =>
- context.GetSelection().Contains(appRef.Selection)
+ var isApplicationQualifier = appObjectDeclaration.References.Any(appRef =>
+ context.GetSelection().Contains(appRef.Selection)
&& appRef.QualifiedModuleName.Equals(reference.QualifiedModuleName));
if (isApplicationQualifier)
@@ -229,6 +230,7 @@ private static string ComponentPropertyValue(IVBComponent component, string prop
return null;
}
- protected override string ResultDescription(IdentifierReference reference, string codeName) => InspectionResults.SheetAccessedUsingStringInspection;
+ protected override string ResultDescription(IdentifierReference reference, string codeName) =>
+ InspectionResults.ResourceManager.GetString(nameof(SheetAccessedUsingStringInspection), CultureInfo.CurrentUICulture);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/StepIsNotSpecifiedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/StepIsNotSpecifiedInspection.cs
index d676e2c984..72548f2f09 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/StepIsNotSpecifiedInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/StepIsNotSpecifiedInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -50,7 +51,7 @@ public StepIsNotSpecifiedInspection(IDeclarationFinderProvider declarationFinder
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.StepIsNotSpecifiedInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(StepIsNotSpecifiedInspection), CultureInfo.CurrentUICulture);
}
private class StepIsNotSpecifiedListener : InspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/StepOneIsRedundantInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/StepOneIsRedundantInspection.cs
index e09cddeb38..355be3e659 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/StepOneIsRedundantInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/StepOneIsRedundantInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -50,7 +51,7 @@ public StepOneIsRedundantInspection(IDeclarationFinderProvider declarationFinder
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.StepOneIsRedundantInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(StepOneIsRedundantInspection), CultureInfo.CurrentUICulture);
}
private class StepOneIsRedundantListener : InspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/StopKeywordInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/StopKeywordInspection.cs
index d9e3b67de3..5199c67778 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/StopKeywordInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/StopKeywordInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -47,7 +48,7 @@ public StopKeywordInspection(IDeclarationFinderProvider declarationFinderProvide
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.StopKeywordInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(StopKeywordInspection), CultureInfo.CurrentUICulture);
}
private class StopKeywordListener : InspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/SuperfluousAnnotationArgumentInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/SuperfluousAnnotationArgumentInspection.cs
index b5d9bc2b15..bc2c6f47e4 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/SuperfluousAnnotationArgumentInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/SuperfluousAnnotationArgumentInspection.cs
@@ -1,5 +1,3 @@
-using System.Collections.Generic;
-using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Results;
using Rubberduck.Parsing;
@@ -9,6 +7,9 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -42,7 +43,7 @@ internal sealed class SuperfluousAnnotationArgumentInspection : InspectionBase
{
public SuperfluousAnnotationArgumentInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override IEnumerable DoGetInspectionResults(DeclarationFinder finder)
{
@@ -80,7 +81,7 @@ private IInspectionResult InspectionResult(IParseTreeAnnotation pta)
private static string ResultDescription(IParseTreeAnnotation pta)
{
return string.Format(
- InspectionResults.SuperfluousAnnotationArgumentInspection,
+ InspectionResults.ResourceManager.GetString(nameof(SuperfluousAnnotationArgumentInspection), CultureInfo.CurrentUICulture),
pta.Annotation.Name);
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/SuspiciousLetAssignmentInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/SuspiciousLetAssignmentInspection.cs
index 59479b8286..f78e5bced5 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/SuspiciousLetAssignmentInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/SuspiciousLetAssignmentInspection.cs
@@ -1,6 +1,4 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.CodeAnalysis.Inspections.Results;
using Rubberduck.Parsing;
@@ -10,6 +8,9 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -126,7 +127,7 @@ private bool IsImplicitDefaultMemberAssignment(IdentifierReference reference)
private IInspectionResult InspectionResult(IdentifierReference lhsReference, IdentifierReference rhsReference, bool isUnbound, DeclarationFinder finder)
{
var disabledQuickFixes = isUnbound
- ? new List {"ExpandDefaultMemberQuickFix"}
+ ? new List { "ExpandDefaultMemberQuickFix" }
: new List();
return new IdentifierReferenceInspectionResult(
this,
@@ -141,7 +142,7 @@ private string ResultDescription(IdentifierReference lhsReference, IdentifierRef
{
var lhsExpression = lhsReference.IdentifierName;
var rhsExpression = rhsReference.IdentifierName;
- return string.Format(InspectionResults.SuspiciousLetAssignmentInspection, lhsExpression, rhsExpression);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(SuspiciousLetAssignmentInspection), CultureInfo.CurrentUICulture), lhsExpression, rhsExpression);
}
private IEnumerable UnboundLhsInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/SuspiciousPredeclaredInstanceAccessInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/SuspiciousPredeclaredInstanceAccessInspection.cs
index 4d02e070bd..53be460197 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/SuspiciousPredeclaredInstanceAccessInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/SuspiciousPredeclaredInstanceAccessInspection.cs
@@ -5,6 +5,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
using Tokens = Rubberduck.Resources.Tokens;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
@@ -75,15 +76,15 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
///
internal sealed class SuspiciousPredeclaredInstanceAccessInspection : IdentifierReferenceInspectionBase
{
- public SuspiciousPredeclaredInstanceAccessInspection(IDeclarationFinderProvider declarationFinderProvider)
+ public SuspiciousPredeclaredInstanceAccessInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
{
}
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
{
- return
- reference.Declaration is ClassModuleDeclaration module &&
+ return
+ reference.Declaration is ClassModuleDeclaration module &&
module.HasPredeclaredId &&
reference.ParentScoping.ParentDeclaration.Equals(module) &&
reference.Context.TryGetAncestor(out var expression) &&
@@ -93,7 +94,7 @@ reference.Declaration is ClassModuleDeclaration module &&
protected override string ResultDescription(IdentifierReference reference)
{
reference.Context.TryGetAncestor(out var expression);
- return string.Format(InspectionResults.SuspiciousPredeclaredInstanceAccessInspection, reference.IdentifierName, expression.GetText());
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(SuspiciousPredeclaredInstanceAccessInspection), CultureInfo.CurrentUICulture), reference.IdentifierName, expression.GetText());
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/KeywordsUsedAsMemberInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/KeywordsUsedAsMemberInspection.cs
index b80fb257e8..b48eaa2fd3 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/KeywordsUsedAsMemberInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/KeywordsUsedAsMemberInspection.cs
@@ -1,12 +1,13 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.InternalApi.Extensions;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.ThunderCode
{
@@ -23,7 +24,7 @@ internal sealed class KeywordsUsedAsMemberInspection : DeclarationInspectionBase
{
public KeywordsUsedAsMemberInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.EnumerationMember, DeclarationType.UserDefinedTypeMember)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -33,11 +34,11 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
protected override string ResultDescription(Declaration declaration)
{
- return InspectionResults.KeywordsUsedAsMemberInspection.ThunderCodeFormat(declaration.IdentifierName);
+ return InspectionResults.ResourceManager.GetString("KeywordsUsedAsMemberInspection", CultureInfo.CurrentUICulture).ThunderCodeFormat(declaration.IdentifierName);
}
// MS-VBAL 3.3.5.2 Reserved Identifiers and IDENTIFIER
- private static readonly IEnumerable ReservedKeywords = new []
+ private static readonly IEnumerable ReservedKeywords = new[]
{
/*
Statement-keyword = "Call" / "Case" /"Close" / "Const"/ "Declare" / "DefBool" / "DefByte" /
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/LineContinuationBetweenKeywordsInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/LineContinuationBetweenKeywordsInspection.cs
index 575e726ab5..112b21e3d8 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/LineContinuationBetweenKeywordsInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/LineContinuationBetweenKeywordsInspection.cs
@@ -5,6 +5,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.ThunderCode
{
@@ -32,7 +33,7 @@ public LineContinuationBetweenKeywordsInspection(IDeclarationFinderProvider decl
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.LineContinuationBetweenKeywordsInspection.ThunderCodeFormat();
+ return InspectionResults.ResourceManager.GetString("LineContinuationBetweenKeywordsInspection", CultureInfo.CurrentUICulture).ThunderCodeFormat();
}
private class LineContinuationBetweenKeywordsListener : InspectionListenerBase
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NegativeLineNumberInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NegativeLineNumberInspection.cs
index 76c391197a..4bf5b0a47d 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NegativeLineNumberInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NegativeLineNumberInspection.cs
@@ -1,5 +1,4 @@
-using System.Linq;
-using Antlr4.Runtime;
+using Antlr4.Runtime;
using Antlr4.Runtime.Tree;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
@@ -8,6 +7,8 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.ThunderCode
{
@@ -31,12 +32,12 @@ public NegativeLineNumberInspection(IDeclarationFinderProvider declarationFinder
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.NegativeLineNumberInspection.ThunderCodeFormat();
+ return InspectionResults.ResourceManager.GetString("NegativeLineNumberInspection", CultureInfo.CurrentUICulture).ThunderCodeFormat();
}
protected override bool IsResultContext(QualifiedContext context, DeclarationFinder finder)
{
- return !IsOnErrorGotoMinusOne(context.Context)
+ return !IsOnErrorGotoMinusOne(context.Context)
|| ProcedureHasMinusOneLabel(finder, context);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NonBreakingSpaceIdentifierInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NonBreakingSpaceIdentifierInspection.cs
index 4987df727c..ca806acab7 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NonBreakingSpaceIdentifierInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NonBreakingSpaceIdentifierInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.ThunderCode
{
@@ -14,13 +15,16 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete.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.
///
+ ///
+ /// You may have discovered this inspection by pasting code directly from a web page, which often contains such non-printable characters.
+ ///
internal sealed class NonBreakingSpaceIdentifierInspection : DeclarationInspectionBase
{
private const string Nbsp = "\u00A0";
public NonBreakingSpaceIdentifierInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -29,7 +33,7 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
protected override string ResultDescription(Declaration declaration)
{
- return InspectionResults.NonBreakingSpaceIdentifierInspection.ThunderCodeFormat(declaration.IdentifierName);
+ return InspectionResults.ResourceManager.GetString("NonBreakingSpaceIdentifierInspection", CultureInfo.CurrentUICulture).ThunderCodeFormat(declaration.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/OnErrorGoToMinusOneInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/OnErrorGoToMinusOneInspection.cs
index 81b1dc4a98..d1f436f130 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/OnErrorGoToMinusOneInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/OnErrorGoToMinusOneInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.ThunderCode
{
@@ -27,7 +28,7 @@ public OnErrorGoToMinusOneInspection(IDeclarationFinderProvider declarationFinde
protected override string ResultDescription(QualifiedContext context)
{
- return InspectionResults.OnErrorGoToMinusOneInspection.ThunderCodeFormat();
+ return InspectionResults.ResourceManager.GetString("OnErrorGoToMinusOneInspection", CultureInfo.CurrentUICulture).ThunderCodeFormat();
}
private class OnErrorGoToMinusOneListener : InspectionListenerBase
@@ -37,13 +38,13 @@ public override void EnterOnErrorStmt(VBAParser.OnErrorStmtContext context)
CheckContext(context, context.expression());
base.EnterOnErrorStmt(context);
}
-
+
private void CheckContext(VBAParser.OnErrorStmtContext context, IParseTree expression)
{
var target = expression?.GetText().Trim() ?? string.Empty;
if (target.StartsWith("-") && int.TryParse(target.Substring(1), out var result) && result == 1)
{
- SaveContext(context);
+ SaveContext(context);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/ThunderCodeFormatExtension.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/ThunderCodeFormatExtension.cs
index b5ff336283..77c16b6179 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/ThunderCodeFormatExtension.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/ThunderCodeFormatExtension.cs
@@ -1,4 +1,5 @@
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.ThunderCode
{
@@ -6,7 +7,7 @@ internal static class ThunderCodeFormatExtension
{
public static string ThunderCodeFormat(this string inspectionBase, params object[] args)
{
- return string.Format(InspectionResults.ThunderCode_Base, string.Format(inspectionBase, args));
+ return string.Format(InspectionResults.ResourceManager.GetString("ThunderCode_Base", CultureInfo.CurrentUICulture), string.Format(inspectionBase, args));
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UDTMemberNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UDTMemberNotUsedInspection.cs
index 9857359cdd..92ed528fc3 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UDTMemberNotUsedInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UDTMemberNotUsedInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
@@ -62,7 +63,7 @@ internal sealed class UDTMemberNotUsedInspection : DeclarationInspectionBase
{
public UDTMemberNotUsedInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.UserDefinedTypeMember)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -75,7 +76,7 @@ protected override string ResultDescription(Declaration declaration)
var declarationType = declaration.DeclarationType.ToLocalizedString();
var declarationName = declaration.IdentifierName;
return string.Format(
- InspectionResults.IdentifierNotUsedInspection,
+ InspectionResults.ResourceManager.GetString(nameof(InspectionResults.IdentifierNotUsedInspection), CultureInfo.CurrentUICulture),
declarationType,
declarationName);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs
index a6cae19f80..47c298853b 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs
@@ -1,6 +1,3 @@
-using System.Collections.Generic;
-using System.Diagnostics.CodeAnalysis;
-using System.Linq;
using Antlr4.Runtime.Misc;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.InternalApi.Extensions;
@@ -11,6 +8,11 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System;
+using System.Collections.Generic;
+using System.Diagnostics.CodeAnalysis;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -50,7 +52,7 @@ internal sealed class UnassignedVariableUsageInspection : IdentifierReferenceIns
{
public UnassignedVariableUsageInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
//See https://github.com/rubberduck-vba/Rubberduck/issues/2010 for why these are being excluded.
private static readonly List IgnoredFunctions = new List
@@ -68,6 +70,7 @@ protected override IEnumerable ObjectionableDeclarations(Declaratio
&& !declaration.IsSelfAssigned
&& finder.MatchName(declaration.AsTypeName)
.All(d => d.DeclarationType != DeclarationType.UserDefinedType)
+ && !declaration.IdentifierName.StartsWith("out", StringComparison.InvariantCultureIgnoreCase)
&& !declaration.References
.Any(reference => reference.IsAssignment)
&& !declaration.References
@@ -136,7 +139,7 @@ private static IEnumerable SingleVariableArgumentSelections(
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
{
return reference != null
- && !IsArraySubscriptAssignment(reference)
+ && !IsArraySubscriptAssignment(reference)
&& !IsArrayReDim(reference);
}
@@ -144,7 +147,7 @@ protected override string ResultDescription(IdentifierReference reference)
{
var identifierName = reference.IdentifierName;
return string.Format(
- InspectionResults.UnassignedVariableUsageInspection,
+ InspectionResults.ResourceManager.GetString(nameof(UnassignedVariableUsageInspection), CultureInfo.CurrentUICulture),
identifierName);
}
@@ -190,7 +193,7 @@ private static bool IsArraySubscriptAssignment(IdentifierReference reference)
var callingExpression = indexExpression.Parent;
- return callingExpression is VBAParser.SetStmtContext
+ return callingExpression is VBAParser.SetStmtContext
|| callingExpression is VBAParser.LetStmtContext;
}
@@ -215,7 +218,7 @@ private bool IsRedimedVariantArrayReference(IdentifierReference reference)
return false;
}
- if(!reference.Context.TryGetAncestor(out var containingMember))
+ if (!reference.Context.TryGetAncestor(out var containingMember))
{
return false;
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UndeclaredVariableInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UndeclaredVariableInspection.cs
index debadc340d..280a9a0706 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UndeclaredVariableInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UndeclaredVariableInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -37,7 +38,7 @@ internal sealed class UndeclaredVariableInspection : DeclarationInspectionBase
{
public UndeclaredVariableInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Variable)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -46,7 +47,7 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.UndeclaredVariableInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(UndeclaredVariableInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnderscoreInPublicClassModuleMemberInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnderscoreInPublicClassModuleMemberInspection.cs
index 739a0543f0..206d568105 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnderscoreInPublicClassModuleMemberInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnderscoreInPublicClassModuleMemberInspection.cs
@@ -3,6 +3,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -37,13 +38,13 @@ internal sealed class UnderscoreInPublicClassModuleMemberInspection : Declaratio
{
public UnderscoreInPublicClassModuleMemberInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Member)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
- return declaration.IdentifierName.Contains("_")
- && (declaration.Accessibility == Accessibility.Public
- || declaration.Accessibility == Accessibility.Implicit)
+ return declaration.IdentifierName.Contains("_")
+ && (declaration.Accessibility == Accessibility.Public
+ || declaration.Accessibility == Accessibility.Implicit)
&& declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.ClassModule)
&& !finder.FindEventHandlers().Contains(declaration)
&& !(declaration is ModuleBodyElementDeclaration member && member.IsInterfaceImplementation);
@@ -51,7 +52,7 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.UnderscoreInPublicClassModuleMemberInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(UnderscoreInPublicClassModuleMemberInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnhandledOnErrorResumeNextInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnhandledOnErrorResumeNextInspection.cs
index d1888fe94c..91b3f19a9b 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnhandledOnErrorResumeNextInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnhandledOnErrorResumeNextInspection.cs
@@ -1,12 +1,13 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -45,13 +46,13 @@ internal sealed class UnhandledOnErrorResumeNextInspection : ParseTreeInspection
public UnhandledOnErrorResumeNextInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
protected override IInspectionListener ContextListener => _listener;
protected override string ResultDescription(QualifiedContext context, IReadOnlyList properties)
{
- return InspectionResults.UnhandledOnErrorResumeNextInspection;
+ return InspectionResults.ResourceManager.GetString(nameof(UnhandledOnErrorResumeNextInspection), CultureInfo.CurrentUICulture);
}
protected override (bool isResult, IReadOnlyList properties) IsResultContextWithAdditionalProperties(QualifiedContext context, DeclarationFinder finder)
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection.cs
index 9e4a45e64b..4685ed1991 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection.cs
@@ -1,9 +1,7 @@
-using System;
-using System.Collections.Generic;
-using System.Linq;
-using Antlr4.Runtime;
+using Antlr4.Runtime;
using Antlr4.Runtime.Misc;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.CodeAnalysis.Inspections.Results;
using Rubberduck.Parsing;
@@ -14,7 +12,10 @@
using Rubberduck.Parsing.VBA.Parsing;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
-using Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation;
+using System;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -136,10 +137,16 @@ public enum CaseInspectionResultType
CaseElse
}
+ public UnreachableCaseInspection(IDeclarationFinderProvider declarationFinderProvider)
+ : this(declarationFinderProvider, null, null)
+ {
+ /* for reflection / default settings */
+ }
+
public UnreachableCaseInspection(
- IDeclarationFinderProvider declarationFinderProvider,
- IUnreachableCaseInspector inspector,
- IParseTreeValueVisitor parseTreeValueVisitor)
+ IDeclarationFinderProvider declarationFinderProvider,
+ IUnreachableCaseInspector inspector,
+ IParseTreeValueVisitor parseTreeValueVisitor)
: base(declarationFinderProvider)
{
_inspector = inspector;
@@ -194,15 +201,15 @@ private static string ResultMessage(CaseInspectionResultType resultType)
switch (resultType)
{
case CaseInspectionResultType.Unreachable:
- return InspectionResults.UnreachableCaseInspection_Unreachable;
+ return InspectionResults.ResourceManager.GetString(nameof(InspectionResults.UnreachableCaseInspection_Unreachable), CultureInfo.CurrentUICulture);
case CaseInspectionResultType.InherentlyUnreachable:
- return InspectionResults.UnreachableCaseInspection_InherentlyUnreachable;
+ return InspectionResults.ResourceManager.GetString(nameof(InspectionResults.UnreachableCaseInspection_InherentlyUnreachable), CultureInfo.CurrentUICulture);
case CaseInspectionResultType.MismatchType:
- return InspectionResults.UnreachableCaseInspection_TypeMismatch;
+ return InspectionResults.ResourceManager.GetString(nameof(InspectionResults.UnreachableCaseInspection_TypeMismatch), CultureInfo.CurrentUICulture);
case CaseInspectionResultType.Overflow:
- return InspectionResults.UnreachableCaseInspection_Overflow;
+ return InspectionResults.ResourceManager.GetString(nameof(InspectionResults.UnreachableCaseInspection_Overflow), CultureInfo.CurrentUICulture);
case CaseInspectionResultType.CaseElse:
- return InspectionResults.UnreachableCaseInspection_CaseElse;
+ return InspectionResults.ResourceManager.GetString(nameof(InspectionResults.UnreachableCaseInspection_CaseElse), CultureInfo.CurrentUICulture);
default:
throw new ArgumentOutOfRangeException(nameof(resultType), resultType, null);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UnrecognizedAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnrecognizedAnnotationInspection.cs
new file mode 100644
index 0000000000..26e129a6e5
--- /dev/null
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UnrecognizedAnnotationInspection.cs
@@ -0,0 +1,54 @@
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.Parsing.Annotations;
+using Rubberduck.Parsing.Symbols;
+using Rubberduck.Parsing.VBA;
+using Rubberduck.Resources.Inspections;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
+
+namespace Rubberduck.CodeAnalysis.Inspections.Concrete
+{
+ ///
+ /// Flags comments that parsed like Rubberduck annotations, but were not recognized as such.
+ ///
+ ///
+ /// Other add-ins may support similar-looking annotations that Rubberduck does not recognize; this inspection can be used to spot a typo in Rubberduck annotations.
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ ///
+ internal sealed class UnrecognizedAnnotationInspection : InvalidAnnotationInspectionBase
+ {
+ public UnrecognizedAnnotationInspection(IDeclarationFinderProvider declarationFinderProvider)
+ : base(declarationFinderProvider) { }
+
+ protected override IEnumerable GetInvalidAnnotations(
+ IEnumerable annotations,
+ IEnumerable userDeclarations,
+ IEnumerable identifierReferences)
+ {
+ return annotations.Where(pta => pta.Annotation is NotRecognizedAnnotation).ToList();
+ }
+
+ protected override string ResultDescription(IParseTreeAnnotation pta) =>
+ string.Format(InspectionResults.ResourceManager.GetString(nameof(UnrecognizedAnnotationInspection), CultureInfo.CurrentUICulture), pta.Context.GetText());
+ }
+}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UntypedFunctionUsageInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UntypedFunctionUsageInspection.cs
index bf32b7a867..73e3e119e9 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UntypedFunctionUsageInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UntypedFunctionUsageInspection.cs
@@ -1,11 +1,12 @@
-using System.Collections.Generic;
-using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -38,7 +39,7 @@ internal sealed class UntypedFunctionUsageInspection : IdentifierReferenceInspec
{
public UntypedFunctionUsageInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
- {}
+ { }
private readonly HashSet _tokens = new HashSet{
Tokens.Error,
@@ -75,7 +76,7 @@ private IEnumerable BuiltInVariantStringFunctionsWithStringTypedVer
{
return finder
.BuiltInDeclarations(DeclarationType.Member)
- .Where(item => item.Scope.StartsWith("VBE7.DLL;")
+ .Where(item => item.Scope.StartsWith("VBE7.DLL;")
&& (_tokens.Contains(item.IdentifierName)
|| item.IdentifierName.StartsWith("_B_var_")
&& _tokens.Contains(item.IdentifierName.Substring("_B_var_".Length))));
@@ -85,7 +86,7 @@ protected override string ResultDescription(IdentifierReference reference)
{
var declarationName = reference.Declaration.IdentifierName;
return string.Format(
- InspectionResults.UntypedFunctionUsageInspection,
+ InspectionResults.ResourceManager.GetString(nameof(UntypedFunctionUsageInspection), CultureInfo.CurrentUICulture),
declarationName);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UseMeaningfulNameInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UseMeaningfulNameInspection.cs
index 9a4d450541..4ca574b2e6 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UseMeaningfulNameInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UseMeaningfulNameInspection.cs
@@ -1,6 +1,4 @@
-using System.Collections.Generic;
-using System.Linq;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.CodeAnalysis.Settings;
using Rubberduck.Parsing.Grammar;
@@ -9,6 +7,9 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Refactorings.Common;
using Rubberduck.SettingsProvider;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -47,11 +48,11 @@ public UseMeaningfulNameInspection(IDeclarationFinderProvider declarationFinderP
_settings = settings;
}
- private static readonly DeclarationType[] IgnoreDeclarationTypes =
+ private static readonly DeclarationType[] IgnoreDeclarationTypes =
{
- DeclarationType.BracketedExpression,
+ DeclarationType.BracketedExpression,
DeclarationType.LibraryFunction,
- DeclarationType.LibraryProcedure,
+ DeclarationType.LibraryProcedure,
};
protected override string[] GlobalInformation(DeclarationFinder finder)
@@ -79,7 +80,7 @@ protected override string ResultDescription(Declaration declaration)
var declarationType = declaration.DeclarationType.ToLocalizedString();
var declarationName = declaration.IdentifierName;
return string.Format(
- Resources.Inspections.InspectionResults.IdentifierNameInspection,
+ Resources.Inspections.InspectionResults.ResourceManager.GetString(nameof(Resources.Inspections.InspectionResults.IdentifierNameInspection), CultureInfo.CurrentUICulture),
declarationType,
declarationName);
}
@@ -89,7 +90,7 @@ protected override ICollection DisabledQuickFixes(Declaration declaratio
return declaration.DeclarationType.HasFlag(DeclarationType.Module)
|| declaration.DeclarationType.HasFlag(DeclarationType.Project)
|| declaration.DeclarationType.HasFlag(DeclarationType.Control)
- ? new List {nameof(QuickFixes.Concrete.IgnoreOnceQuickFix)}
+ ? new List { nameof(QuickFixes.Concrete.IgnoreOnceQuickFix) }
: new List();
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UseOfBangNotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UseOfBangNotationInspection.cs
index a60f47dd47..04270251e9 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UseOfBangNotationInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UseOfBangNotationInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -80,7 +81,7 @@ protected override bool IsResultReference(IdentifierReference reference, Declara
protected override string ResultDescription(IdentifierReference reference)
{
var expression = reference.IdentifierName;
- return string.Format(InspectionResults.UseOfBangNotationInspection, expression);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(UseOfBangNotationInspection), CultureInfo.CurrentUICulture), expression);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UseOfRecursiveBangNotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UseOfRecursiveBangNotationInspection.cs
index 3deb5e6004..588a0a42aa 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UseOfRecursiveBangNotationInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UseOfRecursiveBangNotationInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -90,7 +91,7 @@ protected override bool IsResultReference(IdentifierReference reference, Declara
protected override string ResultDescription(IdentifierReference reference)
{
var expression = reference.IdentifierName;
- return string.Format(InspectionResults.UseOfRecursiveBangNotationInspection, expression);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(UseOfRecursiveBangNotationInspection), CultureInfo.CurrentUICulture), expression);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/UseOfUnboundBangNotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/UseOfUnboundBangNotationInspection.cs
index 3da28ab22f..f9f6ee21ef 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/UseOfUnboundBangNotationInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/UseOfUnboundBangNotationInspection.cs
@@ -1,11 +1,12 @@
-using System.Collections.Generic;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -87,7 +88,7 @@ protected override bool IsResultReference(IdentifierReference reference, Declara
protected override string ResultDescription(IdentifierReference reference)
{
var expression = reference.IdentifierName;
- return string.Format(InspectionResults.UseOfRecursiveBangNotationInspection, expression);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(UseOfRecursiveBangNotationInspection), CultureInfo.CurrentUICulture), expression);
}
}
}
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ValueRequiredInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ValueRequiredInspection.cs
index 24004c3bb5..a3c1200884 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ValueRequiredInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ValueRequiredInspection.cs
@@ -1,10 +1,11 @@
-using System.Collections.Generic;
-using Rubberduck.CodeAnalysis.Inspections.Abstract;
+using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -77,7 +78,7 @@ protected override string ResultDescription(IdentifierReference failedLetCoercio
{
var expression = failedLetCoercion.IdentifierName;
var typeName = failedLetCoercion.Declaration?.FullAsTypeName;
- return string.Format(InspectionResults.ValueRequiredInspection, expression, typeName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(ValueRequiredInspection), CultureInfo.CurrentUICulture), expression, typeName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotAssignedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotAssignedInspection.cs
index a24942a16a..3a5663d3f5 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotAssignedInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotAssignedInspection.cs
@@ -1,4 +1,3 @@
-using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
@@ -6,6 +5,8 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -42,7 +43,7 @@ internal sealed class VariableNotAssignedInspection : DeclarationInspectionBase
{
public VariableNotAssignedInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Variable)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
@@ -51,7 +52,7 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
&& !declaration.IsWithEvents
&& !declaration.IsSelfAssigned
&& !HasUdtType(declaration, finder) // UDT variables don't need to be assigned
- && !declaration.References.Any(reference => reference.IsAssignment
+ && !declaration.References.Any(reference => reference.IsAssignment
|| reference.IsReDim //Ignores Variants used as arrays without assignment of an existing one.
|| IsAssignedByRefArgument(reference.ParentScoping, reference, finder))
&& !IsPublicInExposedClass(declaration);
@@ -113,7 +114,7 @@ private static VBAParser.ArgumentExpressionContext ImmediateArgumentExpressionCo
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.VariableNotAssignedInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(VariableNotAssignedInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotUsedInspection.cs
index 03827a1836..e164a109aa 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotUsedInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotUsedInspection.cs
@@ -1,5 +1,3 @@
-using System.Collections.Generic;
-using System.Linq;
using Antlr4.Runtime;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
@@ -10,6 +8,8 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -49,12 +49,12 @@ internal sealed class VariableNotUsedInspection : DeclarationInspectionBase
///
public VariableNotUsedInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Variable)
- {}
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
// exclude undeclared, see #5439
- return !declaration.IsWithEvents
+ return !declaration.IsWithEvents
&& !declaration.IsUndeclared
&& declaration.References.All(reference => reference.IsAssignment)
&& !declaration.References.Any(IsForLoopAssignment)
@@ -79,7 +79,7 @@ private static bool IsPublicInExposedClass(Declaration procedure)
private bool IsForLoopAssignment(IdentifierReference reference)
{
- if(!reference.IsAssignment)
+ if (!reference.IsAssignment)
{
return false;
}
@@ -104,8 +104,8 @@ protected override string ResultDescription(Declaration declaration)
var declarationType = declaration.DeclarationType.ToLocalizedString();
var declarationName = declaration.IdentifierName;
return string.Format(
- InspectionResults.IdentifierNotUsedInspection,
- declarationType,
+ InspectionResults.ResourceManager.GetString(nameof(InspectionResults.IdentifierNotUsedInspection), CultureInfo.CurrentUICulture),
+ declarationType,
declarationName);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableTypeNotDeclaredInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableTypeNotDeclaredInspection.cs
index 3e0850cff4..1a5ee4fbd2 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableTypeNotDeclaredInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/VariableTypeNotDeclaredInspection.cs
@@ -4,6 +4,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
+using System.Globalization;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -38,14 +39,14 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
internal sealed class VariableTypeNotDeclaredInspection : ImplicitTypeInspectionBase
{
public VariableTypeNotDeclaredInspection(IDeclarationFinderProvider declarationFinderProvider)
- : base(declarationFinderProvider, new []{DeclarationType.Parameter, DeclarationType.Variable}, new[]{DeclarationType.Control})
- {}
+ : base(declarationFinderProvider, new[] { DeclarationType.Parameter, DeclarationType.Variable }, new[] { DeclarationType.Control })
+ { }
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
return base.IsResultDeclaration(declaration, finder)
&& !declaration.IsUndeclared
- && (declaration.DeclarationType != DeclarationType.Parameter
+ && (declaration.DeclarationType != DeclarationType.Parameter
|| declaration is ParameterDeclaration parameter && !parameter.IsParamArray);
}
@@ -54,7 +55,7 @@ protected override string ResultDescription(Declaration declaration)
var declarationType = declaration.DeclarationType.ToLocalizedString();
var declarationName = declaration.IdentifierName;
return string.Format(
- InspectionResults.ImplicitVariantDeclarationInspection,
+ InspectionResults.ResourceManager.GetString(nameof(InspectionResults.ImplicitVariantDeclarationInspection), CultureInfo.CurrentUICulture),
declarationType,
declarationName);
}
diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/WriteOnlyPropertyInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/WriteOnlyPropertyInspection.cs
index 7267a9b1dc..23c6d4ae3a 100644
--- a/Rubberduck.CodeAnalysis/Inspections/Concrete/WriteOnlyPropertyInspection.cs
+++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/WriteOnlyPropertyInspection.cs
@@ -1,11 +1,12 @@
-using System.Collections.Generic;
-using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Linq;
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
@@ -46,7 +47,7 @@ internal sealed class WriteOnlyPropertyInspection : DeclarationInspectionBase
{
public WriteOnlyPropertyInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.PropertyLet, DeclarationType.PropertySet) { }
-
+
protected override IEnumerable DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
{
var setters = RelevantDeclarationsInModule(module, finder)
@@ -71,7 +72,7 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
protected override string ResultDescription(Declaration declaration)
{
- return string.Format(InspectionResults.WriteOnlyPropertyInspection, declaration.IdentifierName);
+ return string.Format(InspectionResults.ResourceManager.GetString(nameof(WriteOnlyPropertyInspection), CultureInfo.CurrentUICulture), declaration.IdentifierName);
}
}
}
diff --git a/Rubberduck.CodeAnalysis/Properties/CodeInspectionDefaults.Designer.cs b/Rubberduck.CodeAnalysis/Properties/CodeInspectionDefaults.Designer.cs
index 8a159534e8..c9be4d29e2 100644
--- a/Rubberduck.CodeAnalysis/Properties/CodeInspectionDefaults.Designer.cs
+++ b/Rubberduck.CodeAnalysis/Properties/CodeInspectionDefaults.Designer.cs
@@ -1,10 +1,10 @@
//------------------------------------------------------------------------------
//
-// Este código fue generado por una herramienta.
-// Versión de runtime:4.0.30319.42000
+// This code was generated by a tool.
+// Runtime Version:4.0.30319.42000
//
-// Los cambios en este archivo podrían causar un comportamiento incorrecto y se perderán si
-// se vuelve a generar el código.
+// Changes to this file may cause incorrect behavior and will be lost if
+// the code is regenerated.
//
//------------------------------------------------------------------------------
@@ -12,7 +12,7 @@ namespace Rubberduck.CodeAnalysis.Properties {
[global::System.Runtime.CompilerServices.CompilerGeneratedAttribute()]
- [global::System.CodeDom.Compiler.GeneratedCodeAttribute("Microsoft.VisualStudio.Editors.SettingsDesigner.SettingsSingleFileGenerator", "16.10.0.0")]
+ [global::System.CodeDom.Compiler.GeneratedCodeAttribute("Microsoft.VisualStudio.Editors.SettingsDesigner.SettingsSingleFileGenerator", "17.12.0.0")]
public sealed partial class CodeInspectionDefaults : global::System.Configuration.ApplicationSettingsBase {
private static CodeInspectionDefaults defaultInstance = ((CodeInspectionDefaults)(global::System.Configuration.ApplicationSettingsBase.Synchronized(new CodeInspectionDefaults())));
@@ -25,129 +25,211 @@ public static CodeInspectionDefaults Default {
[global::System.Configuration.ApplicationScopedSettingAttribute()]
[global::System.Diagnostics.DebuggerNonUserCodeAttribute()]
- [global::System.Configuration.DefaultSettingValueAttribute("\r\n\r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n " +
- " \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n " +
- "\r\n \r\n \r\n \r\n \r\n " +
- " \r\n " +
- "\r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n <" +
- "CodeInspection Name=\"SelfAssignedDeclarationInspection\" Severity=\"Suggestion\" In" +
- "spectionType=\"CodeQualityIssues\" />\r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n \r\n" +
+ " \r\n \r\n " +
+ " \r\n \r\n " +
+ " \r\n \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n " +
+ " \r\n \r\n " +
+ " \r\n \r\n \r\n \r\n \r\n \r\n \r\n <" +
+ "CodeInspection Name=\"ImplicitPublicMemberInspection\" Severity=\"Hint\" InspectionT" +
+ "ype=\"NamingAndConventionsIssues\" />\r\n \r\n " +
+ "\r\n \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n " +
+ "\r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n \r\n \r\n <" +
- "CodeInspection Name=\"AssignmentNotUsedInspection\" Severity=\"Suggestion\" Inspecti" +
- "onType=\"CodeQualityIssues\" />\r\n " +
- "\r\n \r\n \r\n " +
- " \r\n \r\n \r\n \r\n true\r\n")]
+ "duckOpportunities\" />\r\n \r\n \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n " +
+ " \r\n \r\n " +
+ " \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n " +
+ "\r\n \r\n " +
+ " \r\n \r\n \r\n " +
+ " \r\n \r\n \r\n \r\n \r\n \r\n " +
+ " \r\n \r\n " +
+ " \r\n \r\n \r\n \r\n \r\n true\r\n true\r\n " +
+ " \r\n ")]
public global::Rubberduck.CodeAnalysis.Settings.CodeInspectionSettings CodeInspectionSettings {
get {
return ((global::Rubberduck.CodeAnalysis.Settings.CodeInspectionSettings)(this["CodeInspectionSettings"]));
diff --git a/Rubberduck.CodeAnalysis/Properties/CodeInspectionDefaults.settings b/Rubberduck.CodeAnalysis/Properties/CodeInspectionDefaults.settings
index 2112d95f10..e4e74c75ba 100644
--- a/Rubberduck.CodeAnalysis/Properties/CodeInspectionDefaults.settings
+++ b/Rubberduck.CodeAnalysis/Properties/CodeInspectionDefaults.settings
@@ -3,92 +3,136 @@
- <?xml version="1.0" encoding="utf-16"?>
-<CodeInspectionSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema">
- <CodeInspections>
- <CodeInspection Name="BooleanAssignedInIfElseInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="ObsoleteErrorSyntaxInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="StopKeywordInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="UnhandledOnErrorResumeNextInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="EmptyStringLiteralInspection" Severity="Warning" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="ImplicitByRefModifierInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="FunctionReturnValueNotUsedInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="RedundantByRefModifierInspection" Severity="DoNotShow" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="MissingAttributeInspection" Severity="Warning" InspectionType="RubberduckOpportunities" />
- <CodeInspection Name="AttributeOutOfSyncInspection" Severity="Warning" InspectionType="RubberduckOpportunities" />
- <CodeInspection Name="MissingAnnotationArgumentInspection" Severity="Error" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="ModuleScopeDimKeywordInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="MultilineParameterInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="MultipleDeclarationsInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="ObsoleteCallStatementInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="ObsoleteCommentSyntaxInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="ObsoleteLetStatementInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="OptionBaseInspection" Severity="Hint" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="RedundantOptionInspection" Severity="Hint" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="OptionExplicitInspection" Severity="Error" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="ProcedureCanBeWrittenAsFunctionInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="ApplicationWorksheetFunctionInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="AssignedByValParameterInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="EmptyModuleInspection" Severity="Hint" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="LineLabelNotUsedInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="IntegerDataTypeInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="ShadowedDeclarationInspection" Severity="DoNotShow" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="ConstantNotUsedInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="DefaultProjectNameInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="EmptyCaseBlockInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="EmptyDoWhileBlockInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="EmptyElseBlockInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="EmptyForEachBlockInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="EmptyForLoopBlockInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="EmptyIfBlockInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="EmptyWhileWendBlockInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="EncapsulatePublicFieldInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="HostSpecificExpressionInspection" Severity="Warning" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="HungarianNotationInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="ImplicitActiveSheetReferenceInspection" Severity="Warning" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="ImplicitActiveWorkbookReferenceInspection" Severity="Warning" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="ImplicitDefaultMemberAssignmentInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="ImplicitPublicMemberInspection" Severity="Hint" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="ImplicitVariantReturnTypeInspection" Severity="Hint" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="MemberNotOnInterfaceInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="MoveFieldCloserToUsageInspection" Severity="Hint" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="NonReturningFunctionInspection" Severity="Error" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="ObjectVariableNotSetInspection" Severity="Error" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="ObsoleteGlobalInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="ObsoleteTypeHintInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="ParameterCanBeByValInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="ParameterNotUsedInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="ProcedureNotUsedInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="SelfAssignedDeclarationInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="UnassignedVariableUsageInspection" Severity="Error" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="UndeclaredVariableInspection" Severity="Error" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="UntypedFunctionUsageInspection" Severity="Hint" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="UseMeaningfulNameInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="VariableNotAssignedInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="VariableNotUsedInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="VariableTypeNotDeclaredInspection" Severity="Warning" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="WriteOnlyPropertyInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="DefTypeStatementInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="StepIsNotSpecifiedInspection" Severity="DoNotShow" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="StepOneIsRedundantInspection" Severity="Hint" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="SheetAccessedUsingStringInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="ObsoleteMemberUsageInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
- <CodeInspection Name="ObsoleteCallingConventionInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="DuplicatedAnnotationInspection" Severity="Error" InspectionType="RubberduckOpportunities" />
- <CodeInspection Name="ModuleWithoutFolderInspection" Severity="Suggestion" InspectionType="RubberduckOpportunities" />
- <CodeInspection Name="OnLocalErrorInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
- <CodeInspection Name="IsMissingOnInappropriateArgumentInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="IsMissingWithNonArgumentParameterInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="AssignmentNotUsedInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="UnderscoreInPublicClassModuleMemberInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="ExcelUdfNameIsValidCellReferenceInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="EmptyMethodInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="ImplementedInterfaceMemberInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
- <CodeInspection Name="PublicControlFieldAccessInspection" Severity="Hint" InspectionType="LanguageOpportunities" />
- </CodeInspections>
- <WhitelistedIdentifiers />
- <RunInspectionsOnSuccessfulParse>true</RunInspectionsOnSuccessfulParse>
-</CodeInspectionSettings>
+
+ <CodeInspectionSettings xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance">
+ <CodeInspections>
+ <CodeInspection Name="AnnotationInIncompatibleComponentTypeInspection" Severity="Warning" InspectionType="RubberduckOpportunities" />
+ <CodeInspection Name="ApplicationWorksheetFunctionInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="ArgumentWithIncompatibleObjectTypeInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="AssignedByValParameterInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="AssignmentNotUsedInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="AttributeValueOutOfSyncInspection" Severity="Error" InspectionType="RubberduckOpportunities" />
+ <CodeInspection Name="BooleanAssignedInIfElseInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ConstantNotUsedInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="DefaultMemberRequiredInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="DefaultProjectNameInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="DefTypeStatementInspection" Severity="Warning" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="DuplicatedAnnotationInspection" Severity="Error" InspectionType="RubberduckOpportunities" />
+ <CodeInspection Name="EmptyCaseBlockInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="EmptyDoWhileBlockInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="EmptyElseBlockInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="EmptyForEachBlockInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="EmptyForLoopBlockInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="EmptyIfBlockInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="EmptyMethodInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="EmptyModuleInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="EmptyStringLiteralInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="EmptyWhileWendBlockInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="EncapsulatePublicFieldInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="ExcelMemberMayReturnNothingInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ExcelUdfNameIsValidCellReferenceInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="FunctionReturnValueAlwaysDiscardedInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="FunctionReturnValueDiscardedInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="HostSpecificExpressionInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="HungarianNotationInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="IIfSideEffectInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ImplementedInterfaceMemberInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ImplicitActiveSheetReferenceInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ImplicitActiveWorkbookReferenceInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ImplicitByRefModifierInspection" Severity="Hint" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="ImplicitContainingWorkbookReferenceInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ImplicitContainingWorksheetReferenceInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ImplicitDefaultMemberAccessInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ImplicitlyTypedConstInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ImplicitPublicMemberInspection" Severity="Hint" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="ImplicitRecursiveDefaultMemberAccessInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ImplicitUnboundDefaultMemberAccessInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ImplicitVariantReturnTypeInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="InconsistentArrayBaseInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="InconsistentParamArrayBaseInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="IndexedDefaultMemberAccessInspection" Severity="Hint" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="IndexedRecursiveDefaultMemberAccessInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="IndexedUnboundDefaultMemberAccessInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="IntegerDataTypeInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="InvalidAnnotationInspection" Severity="Warning" InspectionType="RubberduckOpportunities" />
+ <CodeInspection Name="IsMissingOnInappropriateArgumentInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="IsMissingWithNonArgumentParameterInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="KeywordsUsedAsMemberInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="LineContinuationBetweenKeywordsInspection" Severity="Error" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="LineLabelNotUsedInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="MemberNotOnInterfaceInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="MisleadingByRefInspection" Severity="Warning" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="MissingAnnotationArgumentInspection" Severity="Error" InspectionType="RubberduckOpportunities" />
+ <CodeInspection Name="MissingAttributeInspection" Severity="Error" InspectionType="RubberduckOpportunities" />
+ <CodeInspection Name="MissingMemberAnnotationInspection" Severity="Warning" InspectionType="RubberduckOpportunities" />
+ <CodeInspection Name="MissingModuleAnnotationInspection" Severity="Warning" InspectionType="RubberduckOpportunities" />
+ <CodeInspection Name="ModuleScopeDimKeywordInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="ModuleWithoutFolderInspection" Severity="Suggestion" InspectionType="RubberduckOpportunities" />
+ <CodeInspection Name="MoveFieldCloserToUsageInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="MultilineParameterInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="MultipleDeclarationsInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="NegativeLineNumberInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="NonBreakingSpaceIdentifierInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="NonReturningFunctionInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ObjectVariableNotSetInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ObjectWhereProcedureIsRequiredInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ObsoleteCallingConventionInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ObsoleteCallStatementInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="ObsoleteCommentSyntaxInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="ObsoleteErrorSyntaxInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="ObsoleteGlobalInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="ObsoleteLetStatementInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="ObsoleteMemberUsageInspection" Severity="Warning" InspectionType="RubberduckOpportunities" />
+ <CodeInspection Name="ObsoleteTypeHintInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="ObsoleteWhileWendStatementInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="OnErrorGoToMinusOneInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="OnLocalErrorInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="OptionBaseInspection" Severity="Hint" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="OptionExplicitInspection" Severity="Error" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="ParameterCanBeByValInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="ParameterlessCellsInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ParameterNotUsedInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ProcedureCanBeWrittenAsFunctionInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="ProcedureNotUsedInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ProcedureRequiredInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="PublicControlFieldAccessInspection" Severity="Hint" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="PublicEnumerationDeclaredInWorksheetInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="ReadOnlyPropertyAssignmentInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="RedundantByRefModifierInspection" Severity="DoNotShow" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="RedundantOptionInspection" Severity="Hint" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="SelfAssignedDeclarationInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="SetAssignmentWithIncompatibleObjectTypeInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="ShadowedDeclarationInspection" Severity="DoNotShow" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="SheetAccessedUsingStringInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="StepIsNotSpecifiedInspection" Severity="DoNotShow" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="StepOneIsRedundantInspection" Severity="Hint" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="StopKeywordInspection" Severity="Hint" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="SuperfluousAnnotationArgumentInspection" Severity="Warning" InspectionType="RubberduckOpportunities" />
+ <CodeInspection Name="SuspiciousLetAssignmentInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="SuspiciousPredeclaredInstanceAccessInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="UDTMemberNotUsedInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="UnassignedVariableUsageInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="UndeclaredVariableInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="UnderscoreInPublicClassModuleMemberInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="UnhandledOnErrorResumeNextInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="UnreachableCaseInspection" Severity="Warning" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="UnrecognizedAnnotationInspection" Severity="Warning" InspectionType="RubberduckOpportunities" />
+ <CodeInspection Name="UntypedFunctionUsageInspection" Severity="Hint" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="UseMeaningfulNameInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="UseOfBangNotationInspection" Severity="Hint" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="UseOfRecursiveBangNotationInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="UseOfUnboundBangNotationInspection" Severity="Warning" InspectionType="NamingAndConventionsIssues" />
+ <CodeInspection Name="ValueRequiredInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="VariableNotAssignedInspection" Severity="Error" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="VariableNotUsedInspection" Severity="Suggestion" InspectionType="CodeQualityIssues" />
+ <CodeInspection Name="VariableTypeNotDeclaredInspection" Severity="Warning" InspectionType="LanguageOpportunities" />
+ <CodeInspection Name="WriteOnlyPropertyInspection" Severity="Suggestion" InspectionType="NamingAndConventionsIssues" />
+ </CodeInspections>
+ <WhitelistedIdentifiers />
+ <RunInspectionsOnSuccessfulParse>true</RunInspectionsOnSuccessfulParse>
+ <IgnoreFormControlsHungarianNotation>true</IgnoreFormControlsHungarianNotation>
+ </CodeInspectionSettings>
+
\ No newline at end of file
diff --git a/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.csproj b/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.csproj
index b39c0b1b32..d49b481a9b 100644
--- a/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.csproj
+++ b/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.csproj
@@ -45,7 +45,7 @@
- 4.6.4
+ 4.6.64.5.10
diff --git a/Rubberduck.CodeAnalysis/Settings/CodeInspectionSettings.cs b/Rubberduck.CodeAnalysis/Settings/CodeInspectionSettings.cs
index e0e5b8f434..e006103f6e 100644
--- a/Rubberduck.CodeAnalysis/Settings/CodeInspectionSettings.cs
+++ b/Rubberduck.CodeAnalysis/Settings/CodeInspectionSettings.cs
@@ -1,10 +1,10 @@
-using System;
+using Rubberduck.CodeAnalysis.Inspections;
+using System;
using System.Collections.Generic;
using System.Configuration;
using System.Globalization;
using System.Linq;
using System.Xml.Serialization;
-using Rubberduck.CodeAnalysis.Inspections;
namespace Rubberduck.CodeAnalysis.Settings
{
@@ -13,6 +13,8 @@ public interface ICodeInspectionSettings
HashSet CodeInspections { get; set; }
WhitelistedIdentifierSetting[] WhitelistedIdentifiers { get; set; }
bool RunInspectionsOnSuccessfulParse { get; set; }
+
+ bool IgnoreFormControlsHungarianNotation { get; set; }
}
[SettingsSerializeAs(SettingsSerializeAs.Xml)]
@@ -26,16 +28,18 @@ public class CodeInspectionSettings : ICodeInspectionSettings, IEquatable(), new WhitelistedIdentifierSetting[] { }, true)
+ public CodeInspectionSettings() : this(Enumerable.Empty(), new WhitelistedIdentifierSetting[] { }, true, false)
{
}
- public CodeInspectionSettings(IEnumerable inspections, WhitelistedIdentifierSetting[] whitelistedNames, bool runInspectionsOnParse)
+ public CodeInspectionSettings(IEnumerable inspections, WhitelistedIdentifierSetting[] whitelistedNames, bool runInspectionsOnParse, bool ignoreFormControlsHungarian)
{
CodeInspections = new HashSet(inspections);
WhitelistedIdentifiers = whitelistedNames;
RunInspectionsOnSuccessfulParse = runInspectionsOnParse;
+ IgnoreFormControlsHungarianNotation = ignoreFormControlsHungarian;
}
public CodeInspectionSetting GetSetting() where TInspection : IInspection
@@ -53,7 +57,7 @@ public CodeInspectionSetting GetSetting(Type inspectionType)
{
return existing;
}
- var proto = Convert.ChangeType(Activator.CreateInstance(inspectionType, new object[]{null}), inspectionType);
+ var proto = Convert.ChangeType(Activator.CreateInstance(inspectionType, new object[] { null }), inspectionType);
var setting = new CodeInspectionSetting(proto as IInspectionModel);
CodeInspections.Add(setting);
return setting;
@@ -69,7 +73,8 @@ public bool Equals(CodeInspectionSettings other)
return other != null &&
CodeInspections.SequenceEqual(other.CodeInspections) &&
WhitelistedIdentifiers.SequenceEqual(other.WhitelistedIdentifiers) &&
- RunInspectionsOnSuccessfulParse == other.RunInspectionsOnSuccessfulParse;
+ RunInspectionsOnSuccessfulParse == other.RunInspectionsOnSuccessfulParse &&
+ IgnoreFormControlsHungarianNotation == other.IgnoreFormControlsHungarianNotation;
}
}
diff --git a/Rubberduck.CodeAnalysis/app.config b/Rubberduck.CodeAnalysis/app.config
index 56c52616a5..e720e2127b 100644
--- a/Rubberduck.CodeAnalysis/app.config
+++ b/Rubberduck.CodeAnalysis/app.config
@@ -18,169 +18,254 @@
-
+
-
-
-
-
+
+
+
-
-
-
+
-
-
-
-
-
-
-
-
-
-
-
-
-
+
-
-
-
-
-
-
-
-
+
+
+
+
-
-
-
-
-
-
-
-
+
+
+
+
+ InspectionType="CodeQualityIssues" />
+
+
+ Severity="Warning" InspectionType="CodeQualityIssues" />
-
+ Severity="Warning" InspectionType="CodeQualityIssues" />
+
+
+
+
+
+
+
+
+
+
+
+
+
+
-
+
+
+
+
+
+
-
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
-
+
+
+
+
-
+
-
-
-
+
-
-
-
-
-
-
-
+
-
-
-
+
+
-
+
-
-
-
-
-
-
+
+
-
+
+
-
-
+
-
-
+
+
+
+
+
+
+
+
+
+ true
+ true
diff --git a/Rubberduck.Core/Properties/Settings.Designer.cs b/Rubberduck.Core/Properties/Settings.Designer.cs
index 90eeb2cf96..1a76b26ed5 100644
--- a/Rubberduck.Core/Properties/Settings.Designer.cs
+++ b/Rubberduck.Core/Properties/Settings.Designer.cs
@@ -12,7 +12,7 @@ namespace Rubberduck.Properties {
[global::System.Runtime.CompilerServices.CompilerGeneratedAttribute()]
- [global::System.CodeDom.Compiler.GeneratedCodeAttribute("Microsoft.VisualStudio.Editors.SettingsDesigner.SettingsSingleFileGenerator", "17.6.0.0")]
+ [global::System.CodeDom.Compiler.GeneratedCodeAttribute("Microsoft.VisualStudio.Editors.SettingsDesigner.SettingsSingleFileGenerator", "17.12.0.0")]
internal sealed partial class Settings : global::System.Configuration.ApplicationSettingsBase {
private static Settings defaultInstance = ((Settings)(global::System.Configuration.ApplicationSettingsBase.Synchronized(new Settings())));
diff --git a/Rubberduck.Core/Rubberduck.Core.csproj b/Rubberduck.Core/Rubberduck.Core.csproj
index cda42e9170..5fdef2e9f1 100644
--- a/Rubberduck.Core/Rubberduck.Core.csproj
+++ b/Rubberduck.Core/Rubberduck.Core.csproj
@@ -65,7 +65,7 @@
- 4.6.4
+ 4.6.65.0.4
diff --git a/Rubberduck.Core/UI/About/AboutControlViewModel.cs b/Rubberduck.Core/UI/About/AboutControlViewModel.cs
index 93272b9980..75720e042a 100644
--- a/Rubberduck.Core/UI/About/AboutControlViewModel.cs
+++ b/Rubberduck.Core/UI/About/AboutControlViewModel.cs
@@ -1,12 +1,12 @@
-using System;
-using System.Diagnostics;
-using Path = System.IO.Path;
-using NLog;
+using NLog;
using NLog.Targets;
using Rubberduck.Resources.About;
using Rubberduck.UI.Command;
using Rubberduck.VersionCheck;
+using System;
+using System.Diagnostics;
using Application = System.Windows.Forms.Application;
+using Path = System.IO.Path;
namespace Rubberduck.UI.About
{
@@ -26,8 +26,11 @@ public AboutControlViewModel(IVersionCheckService version, IWebNavigator web)
public string Version => string.Format(Resources.RubberduckUI.Rubberduck_AboutBuild, _version.VersionString);
- public string OperatingSystem =>
- string.Format(AboutUI.AboutWindow_OperatingSystem, Environment.OSVersion.VersionString, Environment.Is64BitOperatingSystem ? "x64" : "x86");
+ private static readonly string _versionString = Environment.OSVersion.Version.Build > 22000
+ ? $"{Environment.OSVersion.VersionString} (Win11)"
+ : Environment.OSVersion.VersionString;
+
+ public string OperatingSystem => string.Format(AboutUI.AboutWindow_OperatingSystem, _versionString, Environment.Is64BitOperatingSystem ? "x64" : "x86");
public string HostProduct =>
string.Format(AboutUI.AboutWindow_HostProduct, Application.ProductName, Environment.Is64BitProcess ? "x64" : "x86");
@@ -36,7 +39,7 @@ public AboutControlViewModel(IVersionCheckService version, IWebNavigator web)
public string HostExecutable => string.Format(AboutUI.AboutWindow_HostExecutable,
Path.GetFileName(Application.ExecutablePath).ToUpper()); // .ToUpper() used to convert ExceL.EXE -> EXCEL.EXE
-
+
public string AboutCopyright =>
string.Format(AboutUI.AboutWindow_Copyright, DateTime.Now.Year);
@@ -48,11 +51,11 @@ public AboutControlViewModel(IVersionCheckService version, IWebNavigator web)
private void ExecuteViewLog(object parameter)
{
- var fileTarget = (FileTarget) LogManager.Configuration.FindTargetByName("file");
-
- var logEventInfo = new LogEventInfo { TimeStamp = DateTime.Now };
+ var fileTarget = (FileTarget)LogManager.Configuration.FindTargetByName("file");
+
+ var logEventInfo = new LogEventInfo { TimeStamp = DateTime.Now };
var fileName = fileTarget.FileName.Render(logEventInfo);
-
+
// The /select argument will only work if the path has backslashes
fileName = fileName.Replace("/", "\\");
Process.Start(new ProcessStartInfo("explorer.exe", $"/select, \"{fileName}\""));
diff --git a/Rubberduck.Core/UI/Inspections/InspectionResultsControl.xaml b/Rubberduck.Core/UI/Inspections/InspectionResultsControl.xaml
index ab7e4d7bbf..e756d3ad3b 100644
--- a/Rubberduck.Core/UI/Inspections/InspectionResultsControl.xaml
+++ b/Rubberduck.Core/UI/Inspections/InspectionResultsControl.xaml
@@ -97,6 +97,8 @@
+
+
+ content/net40/*
diff --git a/Rubberduck.Interaction/Rubberduck.Interaction.csproj b/Rubberduck.Interaction/Rubberduck.Interaction.csproj
index 56f1006b8e..c712195b7a 100644
--- a/Rubberduck.Interaction/Rubberduck.Interaction.csproj
+++ b/Rubberduck.Interaction/Rubberduck.Interaction.csproj
@@ -20,7 +20,7 @@
- 4.6.4
+ 4.6.6
diff --git a/Rubberduck.Main/Rubberduck.Main.csproj b/Rubberduck.Main/Rubberduck.Main.csproj
index ec05eaae34..bbccf584d8 100644
--- a/Rubberduck.Main/Rubberduck.Main.csproj
+++ b/Rubberduck.Main/Rubberduck.Main.csproj
@@ -65,7 +65,7 @@
- 4.6.4
+ 4.6.64.2.1
diff --git a/Rubberduck.Parsing/Rubberduck.Parsing.csproj b/Rubberduck.Parsing/Rubberduck.Parsing.csproj
index f4209400f9..0092d32fb2 100644
--- a/Rubberduck.Parsing/Rubberduck.Parsing.csproj
+++ b/Rubberduck.Parsing/Rubberduck.Parsing.csproj
@@ -51,7 +51,7 @@
4.6.4
- 4.6.4
+ 4.6.64.5.10
diff --git a/Rubberduck.Refactorings/ReplaceReferences/ReplaceReferencesRefactoringAction.cs b/Rubberduck.Refactorings/ReplaceReferences/ReplaceReferencesRefactoringAction.cs
index 74b3f4cb18..dcbd5fa481 100644
--- a/Rubberduck.Refactorings/ReplaceReferences/ReplaceReferencesRefactoringAction.cs
+++ b/Rubberduck.Refactorings/ReplaceReferences/ReplaceReferencesRefactoringAction.cs
@@ -1,8 +1,8 @@
-using System.Linq;
-using Antlr4.Runtime;
+using Antlr4.Runtime;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Rewriter;
using Rubberduck.Parsing.Symbols;
+using System.Linq;
namespace Rubberduck.Refactorings.ReplaceReferences
{
@@ -38,8 +38,13 @@ public override void Refactor(ReplaceReferencesModel model, IRewriteSession rewr
private (ParserRuleContext context, string replacementName) BuildReferenceReplacementString(IdentifierReference identifierReference, string NewName, bool moduleQualify)
{
+ var qualifier = !moduleQualify ? null :
+ identifierReference.Declaration.DeclarationType == DeclarationType.EnumerationMember
+ ? identifierReference.Declaration.ParentDeclaration.IdentifierName
+ : identifierReference.Declaration.QualifiedModuleName.ComponentName;
+
var replacementExpression = moduleQualify && CanBeModuleQualified(identifierReference)
- ? $"{identifierReference.Declaration.QualifiedModuleName.ComponentName}.{NewName}"
+ ? $"{qualifier}.{NewName}"
: NewName;
return (identifierReference.Context, replacementExpression);
diff --git a/Rubberduck.Refactorings/Rubberduck.Refactorings.csproj b/Rubberduck.Refactorings/Rubberduck.Refactorings.csproj
index 53a04b0db4..f570877afa 100644
--- a/Rubberduck.Refactorings/Rubberduck.Refactorings.csproj
+++ b/Rubberduck.Refactorings/Rubberduck.Refactorings.csproj
@@ -20,7 +20,7 @@
- 4.6.4
+ 4.6.6
diff --git a/Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs b/Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs
index 07db96b0a3..9b5179a1ff 100644
--- a/Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs
+++ b/Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs
@@ -19,7 +19,7 @@ namespace Rubberduck.Resources.Inspections {
// class via a tool like ResGen or Visual Studio.
// To add or remove a member, edit your .ResX file then rerun ResGen
// with the /str option, or rebuild your VS project.
- [global::System.CodeDom.Compiler.GeneratedCodeAttribute("System.Resources.Tools.StronglyTypedResourceBuilder", "16.0.0.0")]
+ [global::System.CodeDom.Compiler.GeneratedCodeAttribute("System.Resources.Tools.StronglyTypedResourceBuilder", "17.0.0.0")]
[global::System.Diagnostics.DebuggerNonUserCodeAttribute()]
[global::System.Runtime.CompilerServices.CompilerGeneratedAttribute()]
public class InspectionInfo {
@@ -438,6 +438,24 @@ public static string ImplicitVariantReturnTypeInspection {
}
}
+ ///
+ /// Looks up a localized string similar to Arrays created with a VBA.Array function call explicitly qualified with the 'VBA' library are always zero-based, regardless of Option Base 1..
+ ///
+ public static string InconsistentArrayBaseInspection {
+ get {
+ return ResourceManager.GetString("InconsistentArrayBaseInspection", resourceCulture);
+ }
+ }
+
+ ///
+ /// Looks up a localized string similar to Arrays created with ParamArray are always zero-based, regardless of Option Base 1..
+ ///
+ public static string InconsistentParamArrayBaseInspection {
+ get {
+ return ResourceManager.GetString("InconsistentParamArrayBaseInspection", resourceCulture);
+ }
+ }
+
///
/// Looks up a localized string similar to A default member access hides away which member is actually called. Although it is apparent that some call is made in the case of an indexed default member access being explicit is usually better for readability..
///
@@ -807,6 +825,15 @@ public static string ParameterCanBeByValInspection {
}
}
+ ///
+ /// Looks up a localized string similar to Get-only property 'Range.Cells' accepts two optional parameters, but if none is supplied then it simply yields a reference to the parent 'Range' object, which makes it entirely redundant..
+ ///
+ public static string ParameterlessCellsInspection {
+ get {
+ return ResourceManager.GetString("ParameterlessCellsInspection", resourceCulture);
+ }
+ }
+
///
/// Looks up a localized string similar to A parameter is passed into a member that does not use it. Consider removing that parameter..
///
@@ -853,7 +880,7 @@ public static string PublicControlFieldAccessInspection {
}
///
- /// Looks up a localized string similar to Copying a worksheet which contains a public Enum declaration will also create a copy of the Enum declaration. The copied declaration will result in an 'Ambiguous name detected' compiler error. Declaring Enumerations in Standard or Class modules avoids unintentional duplication of an Enum declaration..
+ /// Looks up a localized string similar to Copying a worksheet which contains a public Enum declaration will also create a copy of the Enum declaration. The copied declaration will result in an 'Ambiguous name detected' compiler error. Declaring Enumerations in Standard or Class modules avoids unintentional duplication of an Enum declaration..
///
public static string PublicEnumerationDeclaredInWorksheetInspection {
get {
@@ -871,7 +898,7 @@ public static string PublicImplementationShouldBePrivateInspection {
}
///
- /// Looks up a localized string similar to In general, the VBE editor catches this type of error and will not compile. However, there are a few scenarios where the error is overlooked by the compiler and an error is generated at runtime. To avoid a runtime error, implement the missing Property or Subroutine. .
+ /// Looks up a localized string similar to In general, the VBE editor catches this type of error and will not compile. However, there are a few scenarios where the error is overlooked by the compiler and an error is generated at runtime. To avoid a runtime error, implement the missing Property or Subroutine. .
///
public static string ReadOnlyPropertyAssignmentInspection {
get {
@@ -988,7 +1015,7 @@ public static string SuspiciousPredeclaredInstanceAccessInspection {
}
///
- /// Looks up a localized string similar to A User Defined Type (UDT) member is declared but not used. Consider removing the UDT member declaration..
+ /// Looks up a localized string similar to A User Defined Type (UDT) member is declared but not used. Consider removing the UDT member declaration..
///
public static string UDTMemberNotUsedInspection {
get {
diff --git a/Rubberduck.Resources/Inspections/InspectionInfo.cs.resx b/Rubberduck.Resources/Inspections/InspectionInfo.cs.resx
index a2355027ad..47c2fc16f2 100644
--- a/Rubberduck.Resources/Inspections/InspectionInfo.cs.resx
+++ b/Rubberduck.Resources/Inspections/InspectionInfo.cs.resx
@@ -117,15 +117,15 @@
System.Resources.ResXResourceWriter, System.Windows.Forms, Version=4.0.0.0, Culture=neutral, PublicKeyToken=b77a5c561934e089
+
+ Parametr je předán jako hodnota, ale je mu přidělena nová hodnota/reference. Zvažte vytvoření lokální kopie, pokud volaná funkce nemá znát onu novou hodnotu. Pokud má volaná funkce pracovat s novou hodnotou, parametr by měl být předán jako 'ByRef' a vy máte bug.
+
Rubberduck nemůže najít žádnou referenci ke konstantě. Zvažte odstranění nepoužitých deklarací.Zvažte pojmenování vašeho VBA projektu.
-
- Parametr je předán jako hodnota, ale je mu přidělena nová hodnota/reference. Zvažte vytvoření lokální kopie, pokud volaná funkce nemá znát onu novou hodnotu. Pokud má volaná funkce pracovat s novou hodnotou, parametr by měl být předán jako 'ByRef' a vy máte bug.
-
Vestavěná konstanta 'vbNullString' je pointer na prázdný řetězec, který si bere 0 bytů paměti, což jednoznačně vyjadřuje úmysl prázdného řetězce.
@@ -150,6 +150,9 @@
Proměnná na úrovni modulu, která je použita jen v jedné proceduře, by měla být deklarovaná v oné proceduře.
+
+ Rozdělení deklarace parametru na více řádků velmi zraňuje čitelnost. I když je parametr dlouhý, zvažte jeho deklaraci na jeden řádek.
+
Deklarování více proměnných v té samé instrukci je legální, ale nemělo by se to používat často. Zvažte deklaraci proměnných blíže k jejich použití, v jedné instrukci na jednu deklaraci.
@@ -168,20 +171,20 @@
Výraz 'Let' v jazyku existuje pouze pro podporu starých verzí jazyka, které jej potřebují; zde ho můžete bez starostí smazat, protože moderní VBA nepotřebuje klíčové slovo pro přidělení hodnot.
-
- Neexistují žádné reference k proměnné
-
-
- Parametr je předán členu, který jej nevyužívá. Zvažte odstranění tohoto parametru.
+
+ Type nápovědní písmena v jazyku existují jen pro podporu zastaralého kódu, který je vyžaduje; můžou být bez obav nahrazeny deklaracemi jako "As", které specifikují typ explicitně a mohou být vynechány v jiných referencích identifikátoru.
-
- Parametr, který je předán jako reference 'ByRef' a není mu přidělena nová hodnota/reference, může být místo toho předán jako hodnota 'ByVal'.
+
+ Pole typicky začínají nulou. Tato volba změní výchozí spodní hranici pro implicitně definované pole. To může zavést "mimo-o-jednu" typ chyby, pokud na to člověk nedá pozor.VBA s úsměvem na tváři zkompiluje typovou chybu: použijte 'Option Explicit', abyste předešli úspěšné kompilaci programu s chybami.
-
- Pole typicky začínají nulou. Tato volba změní výchozí spodní hranici pro implicitně definované pole. To může zavést "mimo-o-jednu" typ chyby, pokud na to člověk nedá pozor.
+
+ Parametr, který je předán jako reference 'ByRef' a není mu přidělena nová hodnota/reference, může být místo toho předán jako hodnota 'ByVal'.
+
+
+ Parametr je předán členu, který jej nevyužívá. Zvažte odstranění tohoto parametru.Rubberduck nebyl schopen najít žádné volání pro tuto proceduru. Tuto inspekci můžete ignorovat, pokud je procedura přiřazena některému makro tlačítku, použita jako 'user-defined' funkce (UDF) nebo obstarává událost aplikace, o které Rubberduck neví. Pokud se nejedná o žádnou z těchto věcí, zvažte odstranění procedury.
@@ -189,12 +192,6 @@
Zde se jedná nejspíše o bug. Proměnná je referována, avšak nikdy jí není nic přiděleno.
-
- Rozdělení deklarace parametru na více řádků velmi zraňuje čitelnost. I když je parametr dlouhý, zvažte jeho deklaraci na jeden řádek.
-
-
- Type nápovědní písmena v jazyku existují jen pro podporu zastaralého kódu, který je vyžaduje; můžou být bez obav nahrazeny deklaracemi jako "As", které specifikují typ explicitně a mohou být vynechány v jiných referencích identifikátoru.
-
Existuje ekvivalentní funkce, která vrací typ řetězec a měla by být přednostně použita z důvodu vyvarování se implicitního zkonvertování typu.
Jestliže může být parametr prázdný, ignorujte výsledek této inspekce; předání prázdné hodnoty funkci, která očekává řetěz, by vyvolalo "type mismatch" chybu za chodu programu.
@@ -205,6 +202,9 @@ Jestliže může být parametr prázdný, ignorujte výsledek této inspekce; p
Proměnná není přiřazena. Pokud to není záměrem, jedná se pravděpodobně o bug. Ignorujte výsledek této kontroly, pokud je proměnná přiřazena v jiné proceduře pomocí ByRef parametru.
+
+ Neexistují žádné reference k proměnné
+
Proměnná, jejíž typ není explicitně deklarován, je implicitně typu 'Variant'. Pokud to byl váš úmysl, zvažte explicitní deklarování typu 'Variant', nebo deklarujte specifičtější typ.
@@ -214,39 +214,12 @@ Jestliže může být parametr prázdný, ignorujte výsledek této inspekce; p
Procedura, které je způsobem 'ByRef' předán pouze jediný parametr, kterému je před ukončením procedury přiřazena nová hodnota/reference, používá tento ByRef parametr jako návratovou hodnotu: zvažte, zda místo toho nepoužít funkci.
-
- Aplikace Excel již definuje globálně vymezená objektové proměnné s touto referencí. Zvažte použití vlastnosti listu: 'CodeName'.
-
-
- V cyklu for-next je krok 1 jako výchozí a tudíž je nadbytečné ho definovat.
-
-
- V cyklu for-next není specifikován krok. Tohle může být neúmyslné.
-
-
- Používáním 'Def[Type]' výrazu vede ke specifikování typů užitím prefixu. Důrazně odrazujeme od používání tohoto stylu, měli byste se mu vyhnout za každou cenu.
-
-
- Manipulace s chybami by měla být obnovena po použití 'On Error Resume Next'.
-
-
- Prázdné moduly a třídy buďto odkazují na dosud neimplementovanou funkcionalitu, nebo představují zbytečnou zátěž, která může poškodit udržovatelnost projektu.
-
-
- Členu je přiřazen True/False v různých větvích příkazu if bez dalších příkazů v podmínce. Použij místo toho podmínku přímo na člena.
-
-
- Příkaz 'Error' existuje pouze v jazyce, který podporuje starší kód, který jej vyžadoval; používejte radši 'Err.Raise'.
-
-
- V jednom a tom samém scopu existují 2 deklarace, které mají stejný název identifikátoru. To znamená, že bude k dispozici pouze jedna z nich.
-
-
- Prázdný blok 'Loop' bez jakýchkoli spustitelných příkazů ponechává správce kódu ve zmatku, co takový kód vůbec znamená. Vyhněte se psaní kódu, který nemusí být napsán.
-
Deklarace proměnné objektu s automatickým instancí v rozsahu procedur mění, jak funguje nulling reference, což může vést k neočekávanému chování.
+
+ Člen je definován jako funkce, ale ve všech případech je použit jako procedura. Zamyslete se nad zkonvertováním 'Function' na 'Sub'.
+
Rubberduck rozeznává tuto proměnnou jako proměnnou objektu, která je definována bez klíčového slova 'Set'. Tato skutečnost způsobuje run-time chybu 91 'Object or With block variable not set'.
@@ -259,15 +232,48 @@ Jestliže může být parametr prázdný, ignorujte výsledek této inspekce; p
Kód, ve kterém se nacházejí nedeklarované proměnné, a přitom je specifikována volba 'Option Explicit', nelze úspěšně zkompilovat. Nedeklarované proměnné jsou vždy typu Variant, datový typ, který způsobuje zbytečné nároky na výkon a paměť.
-
- Tato metoda je označena jako '@Obsolete'. Neměla by být nadále používána, měla by existovat lepší alternativa.
+
+ Maďarská notace způsobuje menší čitelnost kódu a je zbytečná, pokud jsou proměnné psané velmi jasnou a konkrétní formou.
-
- Klíčové slovo 'Stop' pozdrží exekuci kódu a aktivuje debugger. Vyhněte se tomuto v distribuovanému kódu.
+
+ Přístupové zavolání členu bylo uděláno proti rozšířenému rozhraní, které Rubberduck nemohl vyřešit, nebo nebyl nalezen člen. Pokud VBA nemůže vyřešit typ v době spuštění (run-time), vyskočí chyba 438. Pokud je k dispozici ekvivalentní ne-rozšířené rozhraní, které je schopen Rubberduck vyřešit, zvažte jeho použití.
+
+
+ Závorkové výrazy jsou vyhodnoceny hostitelskou aplikací při běhu (run-time), což znamená, že je VBA nemůže v okamžiku kompilace ověřit. Zvažte místo toho využití objektového modelu hostitelské aplikace.
+
+
+ Objekt Excel Aplikace neimplementuje rozhraní WorksheetFunction napřímo. Všechna volání provedená členy WorksheetFunction jsou zpracována jako 'late bound¨a chyby ve volaném členu budou vráceny jako typ Variant od 'VbVarType.vbError'. Toto zapříčiní nemožnost odchytnout chyby pomocí error handlerů a přidává výkonnostní náročnost ve srovnání s 'early bound' voláním. Zvažte volání 'Application.WorksheetFunction' explicitně. Poznámka: Pokud toto volání v minulosti generovalo chyby, tyto chyby byly ignorovány. Pokud použijete rychlou opravu (Quick fix), měla by být provedena správná manipulace s chybami.
+
+
+ Toto je výchozí nastavení, není třeba jej specifikovat.
+
+
+ Anotaci nelze navázat na požadovaný cíl. Má zde anotace být? Anotaci, kterou je třeba specifikovat na úrovni modulu, nelze použít k anotaci členů; naopak, anotaci, kterou jsou specifikovány členy, nelze použít na úrovni modulu.
+
+
+ Anotace Rubberducku je specifikována pro modul nebo člen, ale příslušný atribut není přítomen. Atributy modulu a anotace je třeba synchronizovat.
+
+
+ Prázdná podmínková větev bez jakýchkoli příkazů nechává osobu, která se na kód pak kouká, tápat, co je vlastně důvodem tohoto kódu. Vyhněte se prosím psaní kódu, který není potřeba být napsán.
+
+
+ Protože je pro tuto možnost nastaveno výchozí/implicitní nastavení, může být tato instrukce bezpečně vynechána.
+
+
+ Ve výchozím nastavení jsou všechny parametry předávány referencí, takže není nutné uvádět 'ByRef' modifikátor.
+
+
+ Označení řádku, na které není nikdy přeskočeno ('GoTo', 'Resume', ...) nemá žádný smysl. Zvažte jeho odstranění.
+
+
+ Prázdná 'Else' smyčka bez jakýchkoli příkazů nechává osobu, která se na kód pak kouká, tápat, co je vlastně důvodem tohoto kódu. Vyhněte se prosím psaní kódu, který není potřeba být napsán.Maximální hodnota 16-bitového (Int) integeru je 32,769 - použitím 32-bit (Long) integeru všude, kde je možné, pomůžete předejít 'Overflow' run-time chybě a je lépe zpracováno moderními CPU.
+
+ Klíčové slovo 'Stop' pozdrží exekuci kódu a aktivuje debugger. Vyhněte se tomuto v distribuovanému kódu.
+
Prázdný 'Case' blok bez jakýchkoli příkazů nechává osobu, která se na kód pak kouká, tápat, co je vlastně důvodem tohoto kódu. Vyhněte se prosím psaní kódu, který není potřeba být napsán.
@@ -280,38 +286,41 @@ Jestliže může být parametr prázdný, ignorujte výsledek této inspekce; p
Prázdná 'For...Next' smyčka bez jakýchkoli příkazů nechává osobu, která se na kód pak kouká, tápat, co je vlastně důvodem tohoto kódu. Vyhněte se prosím psaní kódu, který není potřeba být napsán.
-
- Prázdná 'Else' smyčka bez jakýchkoli příkazů nechává osobu, která se na kód pak kouká, tápat, co je vlastně důvodem tohoto kódu. Vyhněte se prosím psaní kódu, který není potřeba být napsán.
+
+ Prázdný blok 'Loop' bez jakýchkoli spustitelných příkazů ponechává správce kódu ve zmatku, co takový kód vůbec znamená. Vyhněte se psaní kódu, který nemusí být napsán.
-
- Prázdná podmínková větev bez jakýchkoli příkazů nechává osobu, která se na kód pak kouká, tápat, co je vlastně důvodem tohoto kódu. Vyhněte se prosím psaní kódu, který není potřeba být napsán.
+
+ V jednom a tom samém scopu existují 2 deklarace, které mají stejný název identifikátoru. To znamená, že bude k dispozici pouze jedna z nich.
-
- Maďarská notace způsobuje menší čitelnost kódu a je zbytečná, pokud jsou proměnné psané velmi jasnou a konkrétní formou.
+
+ Příkaz 'Error' existuje pouze v jazyce, který podporuje starší kód, který jej vyžadoval; používejte radši 'Err.Raise'.
-
- Protože je pro tuto možnost nastaveno výchozí/implicitní nastavení, může být tato instrukce bezpečně vynechána.
+
+ Členu je přiřazen True/False v různých větvích příkazu if bez dalších příkazů v podmínce. Použij místo toho podmínku přímo na člena.
-
- Ve výchozím nastavení jsou všechny parametry předávány referencí, takže není nutné uvádět 'ByRef' modifikátor.
+
+ Prázdné moduly a třídy buďto odkazují na dosud neimplementovanou funkcionalitu, nebo představují zbytečnou zátěž, která může poškodit udržovatelnost projektu.
-
- Označení řádku, na které není nikdy přeskočeno ('GoTo', 'Resume', ...) nemá žádný smysl. Zvažte jeho odstranění.
+
+ Podmínka 'Case' se buď vždy vyhodnotí jako False, způsobí run-time chybu, nebo nakumulovaný efekt předchozích 'Case' výrazů představuje všechny možné hodnoty nebo nadmnožinu hodnot výrazu 'Case'. Důsledkem toho je, že se 'Case' blok nikdy nevykoná a je tedy "mrtvý kód", nebo je výraz 'Case' velmi náchylná k run-time chybě, která s velkou pravděpodobností nastane. Zvažte odstranění, změnu pořadí nebo úpravu výrazu 'Case'.
-
- Anotace Rubberducku je specifikována pro modul nebo člen, ale příslušný atribut není přítomen. Atributy modulu a anotace je třeba synchronizovat.
+
+ Manipulace s chybami by měla být obnovena po použití 'On Error Resume Next'.
-
- Toto je výchozí nastavení, není třeba jej specifikovat.
+
+ Používáním 'Def[Type]' výrazu vede ke specifikování typů užitím prefixu. Důrazně odrazujeme od používání tohoto stylu, měli byste se mu vyhnout za každou cenu.
-
- Přístupové zavolání členu bylo uděláno proti rozšířenému rozhraní, které Rubberduck nemohl vyřešit, nebo nebyl nalezen člen. Pokud VBA nemůže vyřešit typ v době spuštění (run-time), vyskočí chyba 438. Pokud je k dispozici ekvivalentní ne-rozšířené rozhraní, které je schopen Rubberduck vyřešit, zvažte jeho použití.
+
+ V cyklu for-next není specifikován krok. Tohle může být neúmyslné.
-
- Závorkové výrazy jsou vyhodnoceny hostitelskou aplikací při běhu (run-time), což znamená, že je VBA nemůže v okamžiku kompilace ověřit. Zvažte místo toho využití objektového modelu hostitelské aplikace.
+
+ V cyklu for-next je krok 1 jako výchozí a tudíž je nadbytečné ho definovat.
-
- Objekt Excel Aplikace neimplementuje rozhraní WorksheetFunction napřímo. Všechna volání provedená členy WorksheetFunction jsou zpracována jako 'late bound¨a chyby ve volaném členu budou vráceny jako typ Variant od 'VbVarType.vbError'. Toto zapříčiní nemožnost odchytnout chyby pomocí error handlerů a přidává výkonnostní náročnost ve srovnání s 'early bound' voláním. Zvažte volání 'Application.WorksheetFunction' explicitně. Poznámka: Pokud toto volání v minulosti generovalo chyby, tyto chyby byly ignorovány. Pokud použijete rychlou opravu (Quick fix), měla by být provedena správná manipulace s chybami.
+
+ Aplikace Excel již definuje globálně vymezená objektové proměnné s touto referencí. Zvažte použití vlastnosti listu: 'CodeName'.
+
+
+ Tato metoda je označena jako '@Obsolete'. Neměla by být nadále používána, měla by existovat lepší alternativa.Windows implemenace Visual Basic podporuje pouze StdCall volací konvenci a použití CDecl volací konvence je podporováno pouze ve verzích VBA systému Macintosh. Použití tohoto klíčového slova ve Windows může mít za následek chybu runtime 49 - 'Bad DLL calling convention'. Pokud je tato procedura určena pouze pro hostitele systému Macintosh, měla by být podmíněně zkompilována.
@@ -322,36 +331,36 @@ Jestliže může být parametr prázdný, ignorujte výsledek této inspekce; p
Moduly bez '@Folder' anotace nelze v Code Exploreru uživatelsky seskupovat do skupin.
+
+ Chyba 'On Local Error' existuje pouze kvůli kompatibilitě s předchozími verzemi Visual Basic a se všemi chybami je zacházeno jako s Lokálními. Chybné použití tohoto klíčového slova může navodit dojem, že existuje rozdíl mezi typy zpracování chyb a přitom nic takového není.
+
+
+ IsMissing je určeno pouze pro volání volitelných argumentů a správné výsledky vrátí pouze v případě, jestliže je typ argumenty 'Variant' bez explicitní výchozí hodnoty. Všechna jiná použití vrátí 'False'.
+
+
+ 'IsMissing' je určen pouze k tomu, aby byl volán argumenty procedury a téměř všechny ostatní vrátí 'False'. Předávání jakéhokoli jiného výrazu do funkce je ekvivalentní k 'VarType({expression}) = vbError' a ve vzácných případech může způsobit selhání hostitelské aplikace.
+
Přiřazení je okamžitě přepsáno jiným přiřazením nebo na něj není nikdy odkazováno.
+
+ Modul třídy, který obsahuje členy s podtržítky, nemůže být implementován jinými třídy. Podtržítko je používáno jako oddělovač mezi názvem rozhraní/objektem a implementovaným jménem členu: podtržítko v názvu člena zmate kompilátor, který pak odmítá zkompilování projektu. Vyhněte se podtržítkům v názvech veřejných členů a řiďte se konvencí pojmenování dle 'PascalCase'.
+
Je možné, že procedura vracející objekt, může vrátit 'Nothing'. Toto způsobí runtime chybu 91 - "Proměnná objektu nebo bloku With není nastavena" u přístupu následujícího člena. Proveďte kontrolu na 'Is Nothing' po zadání 'Set', aby se těmto chybám předešlo.
+
+ Funkce, které jsou pro Excel viditelné jako funkce 'definované uživatelem', vrátí chybu 'REF!', pokud jsou použity ve Worksheetu a jestli odpovídají názvu platného odkazu na buňku. Pokud je funkce zamyšlena k použití jako UDF, musí být přejmenována. Není-li tato funkce míněna jako UDF, měla by být zařazena jako 'Privátní' nebo přesunuta pryč ze standardního modulu.
+
Anotace Rubberducku je určena pro modul nebo člen, ale příslušný atribut má jinou hodnotu. Atributy modulu a anotace musejí být synchronizovány.
-
- IsMissing je určeno pouze pro volání volitelných argumentů a správné výsledky vrátí pouze v případě, jestliže je typ argumenty 'Variant' bez explicitní výchozí hodnoty. Všechna jiná použití vrátí 'False'.
-
Atributy členu se nezobrazují ve VBE. Přidáním anotace uděláte tyto atributy více explicitní a Rubberduck bude moci držet anotace a atributy synchronizovány.Atribudy modulu se nezobrazují ve VBE. Přidáním anotace uděláte tyto atributy více explicitní a Rubberduck bude moci držet anotace a atributy synchronizovány.
-
- Chyba 'On Local Error' existuje pouze kvůli kompatibilitě s předchozími verzemi Visual Basic a se všemi chybami je zacházeno jako s Lokálními. Chybné použití tohoto klíčového slova může navodit dojem, že existuje rozdíl mezi typy zpracování chyb a přitom nic takového není.
-
-
- 'IsMissing' je určen pouze k tomu, aby byl volán argumenty procedury a téměř všechny ostatní vrátí 'False'. Předávání jakéhokoli jiného výrazu do funkce je ekvivalentní k 'VarType({expression}) = vbError' a ve vzácných případech může způsobit selhání hostitelské aplikace.
-
-
- Modul třídy, který obsahuje členy s podtržítky, nemůže být implementován jinými třídy. Podtržítko je používáno jako oddělovač mezi názvem rozhraní/objektem a implementovaným jménem členu: podtržítko v názvu člena zmate kompilátor, který pak odmítá zkompilování projektu. Vyhněte se podtržítkům v názvech veřejných členů a řiďte se konvencí pojmenování dle 'PascalCase'.
-
-
- Funkce, které jsou pro Excel viditelné jako funkce 'definované uživatelem', vrátí chybu 'REF!', pokud jsou použity ve Worksheetu a jestli odpovídají názvu platného odkazu na buňku. Pokud je funkce zamyšlena k použití jako UDF, musí být přejmenována. Není-li tato funkce míněna jako UDF, měla by být zařazena jako 'Privátní' nebo přesunuta pryč ze standardního modulu.
-
Klíčové slovo se používá jako člen v enumeraci, nebo v uživatelem definovaném typu. To může vést k nejednoznačnému řešení. Zvažte přejmenování člena.
@@ -370,21 +379,6 @@ Jestliže může být parametr prázdný, ignorujte výsledek této inspekce; p
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'.
-
- Vykřičníková notace, formálně známá jako výraz přístupu ke slovníku, vypadá, že je silně zadaná. Ve skutečnosti je to však striktně zadaný přístup k parametrizovanému výchozímu členu objektu, na kterém je použit. Obzvláště zavádějící, pokud výchozí parametrizovaný člen není na samotném objektu a lze jej vyvolat pouze zavoláním výchozího člena bez parametrů.
-
-
- Vykřičníková notace, formálně známá jako výraz přístupu ke slovníku, vypadá, že je silně zadaná. Ve skutečnosti je to však striktně zadaný přístup k parametrizovanému výchozímu členu objektu, na kterém je použit.
-
-
- Vykřičníková notace, formálně známá jako výraz přístupu ke slovníku, vypadá, že je silně zadaná. Ve skutečnosti je to však striktně zadaný přístup k parametrizovanému výchozímu členu objektu, na kterém je použit. Obzvláště zavádějící, že není možné určit výchozího člena při kompilaci.
-
-
- Výchozí členský přístup skryje, který člen je skutečně volán. I když je zřejmé, že se některé volání provádí v případě, že je indexovaný výchozí členský přístup explicitní, což je obvykle lepší pro čitelnost.
-
-
- Podmínka 'Case' se buď vždy vyhodnotí jako False, způsobí run-time chybu, nebo nakumulovaný efekt předchozích 'Case' výrazů představuje všechny možné hodnoty nebo nadmnožinu hodnot výrazu 'Case'. Důsledkem toho je, že se 'Case' blok nikdy nevykoná a je tedy "mrtvý kód", nebo je výraz 'Case' velmi náchylná k run-time chybě, která s velkou pravděpodobností nastane. Zvažte odstranění, změnu pořadí nebo úpravu výrazu 'Case'.
-
Kompilátor VBA nezpůsobí chybu, pokud je objekt přiřazen k proměnné s nekompatibilním deklarovaným typem objektu, tj. s typem, který není ani ten samý typ, supertyp ani subtyp. Téměř za všech okolností takové přirazení vede k chybě run-time, kterou je těžší detekovat a tento kód tedy indikuje chybu. Ve všech ostatních situacích lze kód změnit tak, aby používal pouze přiřazení mezi kompatibilními deklarovanými typy.
@@ -406,9 +400,21 @@ Jestliže může být parametr prázdný, ignorujte výsledek této inspekce; p
Kompilátor VBA nezpůsobí chybu, pokud je vyžadováno výchozí indexované volání člena, ale deklarovaný typ objektu nemá vhodný výchozí člen. Toto vede téměř za všech okolností k run-time chybě 91 'Object or With block variable not set' nebo chybě 438 'Object doesn't support this property or method' v závislosti na tom, zda má objekt hodnotu 'Nothing' nebo ne. Toto je těžké detekovat a indikuje to tedy chybu.
+
+ Vykřičníková notace, formálně známá jako výraz přístupu ke slovníku, vypadá, že je silně zadaná. Ve skutečnosti je to však striktně zadaný přístup k parametrizovanému výchozímu členu objektu, na kterém je použit.
+
+
+ Vykřičníková notace, formálně známá jako výraz přístupu ke slovníku, vypadá, že je silně zadaná. Ve skutečnosti je to však striktně zadaný přístup k parametrizovanému výchozímu členu objektu, na kterém je použit. Obzvláště zavádějící, pokud výchozí parametrizovaný člen není na samotném objektu a lze jej vyvolat pouze zavoláním výchozího člena bez parametrů.
+
+
+ Vykřičníková notace, formálně známá jako výraz přístupu ke slovníku, vypadá, že je silně zadaná. Ve skutečnosti je to však striktně zadaný přístup k parametrizovanému výchozímu členu objektu, na kterém je použit. Obzvláště zavádějící, že není možné určit výchozího člena při kompilaci.
+
Použití objektu s výchozím členem v místě, které vyžaduje proceduru, vede k implicitnímu vyvolání výchozího člena. Toto je s největší pravděpodobností neúmyslné a negativně ovlivňuje čitelnost.
+
+ Výchozí členský přístup skryje, který člen je skutečně volán. I když je zřejmé, že se některé volání provádí v případě, že je indexovaný výchozí členský přístup explicitní, což je obvykle lepší pro čitelnost.
+
Výchozí přístup člena skryje, který člen je skutečně volán. I když je zřejmé, že se některé volání provádí v případě, že je indexovaný výchozí přístup člena explicitní, je obvykle lepší pro čitelnost. To platí zejména případě, že přistupovaný výchozí člen není interface samotného objektu, ale musí být vyřešen prostřednictvím řetězce výchozích členských volání.
@@ -428,34 +434,28 @@ Jestliže může být parametr prázdný, ignorujte výsledek této inspekce; p
Kdykoli jsou obě strany přiřazení bez 'Set' typu Objekt, existuje přiřazení od výchozího člena RHS k druhému - LHS. I
když by toto mohlo být úmyslné, v mnoha situacích to jen maskuje chybně zapomenuté klíčové slovo 'Set'.
-
- Člen je definován jako funkce, ale ve všech případech je použit jako procedura. Zamyslete se nad zkonvertováním 'Function' na 'Sub'.
-
-
- Anotace má více argumentů, než je povoleno; nadbytečné argumenty jsou ignorovány.
-
Vrácená hodnota z funkce je zahozena, tzn. funkce je použita jako 'Sub' procedura. Toto je buď nepozornost, nebo je funkce použita pro její vedlejší účinek, což zavání špatným kódem.Pokud není definována klausule typu 'As' pro deklaraci 'Const', použije se implicitní typ. Explicitně definujte ' As <Type>', kde '<Type>' je korektní data typ hodnoty konstanty.
-
- Komentář byl parsován jako syntakticky platná anotace, ale nebyl rozpoznán jako podporovaný typ anotace.
+
+ Anotace má více argumentů, než je povoleno; nadbytečné argumenty jsou ignorovány.
+
+
+ Implicitní odkazy na členy sešitu uvnitř modulu dokumentu sešitu lze chybně zaměnit za implicitní odkazy na aktivní sešit, což je normální chování ve všech ostatních modulech. Tím, že explicitně kvalifikujete tato volání členů s 'Me', lze vyřešit tuto dvojznačnost. Pokud byl záměr odkazovat na aktivní sešit, abyste předešli chybám, kvalifikujte volání na 'ActiveWorkbook'.
+
+
+ Implicitní odkazy na členy listu uvnitř modulu dokumentu listu lze chybně zaměnit za implicitní odkazy na aktivní list, což je normální chování ve všech ostatních modulech. Tím, že explicitně kvalifikujete tato volání členů s 'Me', lze vyřešit tuto dvojznačnost. Pokud byl záměr odkazovat na aktivní list, abyste předešli chybám, kvalifikujte volání na 'ActiveSheet'.Poslední parametr (parametr 'Value') mutátorů vlastností (Let/Set) je vždy předán jako ByVal. To platí bez ohledu na přítomnost nebo absenci ByRef/ByVal modifikátorů. Výjimka: UserDefinedType musí být vždy předán jako ByRef, i když se jedná o poslední parametr mutátoru vlastní.
-
- Anotaci nelze navázat na požadovaný cíl. Má zde anotace být? Anotaci, kterou je třeba specifikovat na úrovni modulu, nelze použít k anotaci členů; naopak, anotaci, kterou jsou specifikovány členy, nelze použít na úrovni modulu.
-
V typu modulu, ve kterém není možno specifikovat anotaci, byla specifikována anotace. Některé anotace lze použít pouze u specifických typech modulů. U jiných toto nelze.
-
- Implicitní odkazy na členy sešitu uvnitř modulu dokumentu sešitu lze chybně zaměnit za implicitní odkazy na aktivní sešit, což je normální chování ve všech ostatních modulech. Tím, že explicitně kvalifikujete tato volání členů s 'Me', lze vyřešit tuto dvojznačnost. Pokud byl záměr odkazovat na aktivní sešit, abyste předešli chybám, kvalifikujte volání na 'ActiveWorkbook'.
-
-
- Implicitní odkazy na členy listu uvnitř modulu dokumentu listu lze chybně zaměnit za implicitní odkazy na aktivní list, což je normální chování ve všech ostatních modulech. Tím, že explicitně kvalifikujete tato volání členů s 'Me', lze vyřešit tuto dvojznačnost. Pokud byl záměr odkazovat na aktivní list, abyste předešli chybám, kvalifikujte volání na 'ActiveSheet'.
+
+ Komentář byl parsován jako syntakticky platná anotace, ale nebyl rozpoznán jako podporovaný typ anotace.
\ No newline at end of file
diff --git a/Rubberduck.Resources/Inspections/InspectionInfo.de.resx b/Rubberduck.Resources/Inspections/InspectionInfo.de.resx
index b235358ab4..9d4134c09e 100644
--- a/Rubberduck.Resources/Inspections/InspectionInfo.de.resx
+++ b/Rubberduck.Resources/Inspections/InspectionInfo.de.resx
@@ -138,6 +138,9 @@
Implizite Referenzen zur aktuellen Arbeitsmappe macht den Code anfällig und schwieriger zu debuggen. Erwäge die Referenz explizit anzugeben oder vorzugsweise mit Objektreferenzen zu arbeiten. Ignoriere wenn der Methodenaufruf sich auf einen Typ bezieht, den Rubberduck nicht auflösen kann.
+
+ Parameter werden, falls nicht anders spezifiziert, als Referenz übergeben. Dies kann verwirrend sein und Bugs hervorrufen. Bevorzugen Sie die Übergabe von Parametern als Werte und spezifizieren Sie eine Referenzübergabe explizit als ByRef.
+
Die Methoden eines Moduls sind standardmäßig öffentlich, was irreführend sein kann. Besser ist es, den Gültigkeitsbereich der Methoden explizit zu definieren.
@@ -214,44 +217,38 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
Eine selbstzugewiesene Objektvariablendeklaration in einer Prozedur kann das Verhalten beim Nulling verändern. Dies kann zu unvorhergesehen Verhalten des Codes führen.
+
+ Ein Element ist als Funktion geschrieben, wird aber überall wie eine Prozedur verwendet. Sie sollten in Erwägung ziehen die 'Function' in ein 'Sub' zu konvertieren.
+
Rubberduck hat festgestellt, dass die Variable eine Objektvariable ist, die ohne 'Set'-Schlüsselwort zugewiesen wird. Dies führt zu dem Laufzeitfehler 91 'Objektvariable oder With-Blockvariable nicht festgelegt' oder 438 'Objekt unterstützt diese Eigenschaft oder Methode nicht' abhängig davon, ob die Variable den Wert 'Nothing' hat oder nicht.Einer Annotation in einem Kommentar fehlt ein Argument oder sie konnte nicht gelesen werden. Die korrekte Syntax ist: '@Annotation([parameter])'\nBeispiel: '@Folder("Parent.Child")'
-
- Code, der undeklarierte Variablen verwendet, kompiliert nicht wenn 'Option Explicit' spezifiziert wird. Undeklarierte Variablen sind immer vom Typ 'Variant', was unnötige Zusatzkosten in Ausführungszeit und Speicherverbauch verursacht.
-
Das Schlüsselwort 'Public' kann nur auf Modulebene verwendet werden; Sein Konterpart 'Private' kann auch nur auf Modulebene verwendet werden. 'Dim' jedoch kann verwendet werden, um sowohl modulweite als auch prozedurweite Variablen zu deklarieren. Um der Konsistenz Willen ist es besser, 'Dim' nur für lokale Variablen zu verwenden, also 'Private' statt 'Dim' auf Modulebene zu verwenden.
-
- Ein Element ist als Funktion geschrieben, wird aber überall wie eine Prozedur verwendet. Sie sollten in Erwägung ziehen die 'Function' in ein 'Sub' zu konvertieren.
-
-
- Es wird ein Elementzugriff verwendet, der vom Interface des Objektes nicht deklariert wird. Dies ist höchstwahrscheinlich ein Fehler. Falls der Elementzugriff das erweiterbare Interface des Objektes verwendet, erwägen Sie ein nicht erweiterbares Äquivalent zu verwenden um Prüfungen zur Kompilierzeit zu ermöglichen und das Auftreten von Laufzeitfehler 438 zu verhindern.
+
+ Code, der undeklarierte Variablen verwendet, kompiliert nicht wenn 'Option Explicit' spezifiziert wird. Undeklarierte Variablen sind immer vom Typ 'Variant', was unnötige Zusatzkosten in Ausführungszeit und Speicherverbauch verursacht.'Ungarische Notation' macht Code weniger lesbar und ist redundant, sobald stark typisierte Variablen und aussagekräftige Namen verwendet werden.
-
- Das Excel Application-Objekt implementiert das WorksheetFunction Interface nicht direkt. Alle Aufrufe an WorksheetFunction Elemente werden als spät gebunden behandelt und Fehler im aufgerufenen Element werden in ein Variant des Typs VbVarType.Error gekapselt. Dadurch können Fehler nicht mit Fehleranweisungen behandelt werden und gegenüber früh gebundenen Aufrufen sinkt die Performanz. Ziehen Sie in Erwägung Application.WorksheetFunction explizit aufzurufen. Bedenken Sie: Falls dieser Aufruf in der Vergangenheit Fehler erzeugt hat, wurden diese ignoriert. Es sollte eine Fehlerbehandlung vorhanden sein, bevor Sie die schnelle Korrektur anwenden.
+
+ Es wird ein Elementzugriff verwendet, der vom Interface des Objektes nicht deklariert wird. Dies ist höchstwahrscheinlich ein Fehler. Falls der Elementzugriff das erweiterbare Interface des Objektes verwendet, erwägen Sie ein nicht erweiterbares Äquivalent zu verwenden um Prüfungen zur Kompilierzeit zu ermöglichen und das Auftreten von Laufzeitfehler 438 zu verhindern.Geklammerte Ausdrücke werden von der Hostanwendung zur Laufzeit ausgewertet, was bedeutet, dass VBA den Ausdruck nicht zur Kompilierzeit validieren kann. Erwägen sie, das hostspezifische Objektmodell zu verwenden.
+
+ Das Excel Application-Objekt implementiert das WorksheetFunction Interface nicht direkt. Alle Aufrufe an WorksheetFunction Elemente werden als spät gebunden behandelt und Fehler im aufgerufenen Element werden in ein Variant des Typs VbVarType.Error gekapselt. Dadurch können Fehler nicht mit Fehleranweisungen behandelt werden und gegenüber früh gebundenen Aufrufen sinkt die Performanz. Ziehen Sie in Erwägung Application.WorksheetFunction explizit aufzurufen. Bedenken Sie: Falls dieser Aufruf in der Vergangenheit Fehler erzeugt hat, wurden diese ignoriert. Es sollte eine Fehlerbehandlung vorhanden sein, bevor Sie die schnelle Korrektur anwenden.
+
Dies ist die Standardeinstellung, sie muss nicht spezifiziert werden.
-
- Da dies die Standardeinstellung für diese Option ist, kann die Anweisung ohne Nebeneffekte entfernt werden.
-
-
- Alle Parameter werden, falls nicht anders spezifiziert als Referenz übergeben. Es ist also nicht nötig, die 'ByRef'-Markierung zu verwenden.
-
-
- Parameter werden, falls nicht anders spezifiziert, als Referenz übergeben. Dies kann verwirrend sein und Bugs hervorrufen. Bevorzugen Sie die Übergabe von Parametern als Werte und spezifizieren Sie eine Referenzübergabe explizit als ByRef.
+
+ Die Annotation konnte keinem Ziel zugewiesen werden. Eine Annotation für die Modulebene kann nicht verwendet werden, um Elemente zu annotieren. Eine Annotation für Elemente kann auf Modulebene nicht verwendet werden. Modul- und Elementannotationen sollten nur einmal spezifiziert werden.Eine Rubberduck-Annotation wurde für ein Modul oder Element festgelegt, aber das zugehörige Attribut fehlt. Die Modul-Attribute und Annotationen sollten synchronisiert werden.
@@ -259,14 +256,20 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
Ein leerer 'If'-Block ohne ausführbare Anweisungen lässt andere Entwickler über die Absicht des Codes im unklaren. Vermeiden Sie das Schreiben von unnötigem Code.
+
+ Da dies die Standardeinstellung für diese Option ist, kann die Anweisung ohne Nebeneffekte entfernt werden.
+
+
+ Alle Parameter werden, falls nicht anders spezifiziert als Referenz übergeben. Es ist also nicht nötig, die 'ByRef'-Markierung zu verwenden.
+
Rubberduck konnte keine Resume oder GoTo Anweisung zu einer Zeilenbezeichnung finden. Erwägen Sie eine Entfernung der Bezeichnung.
-
- Eine leere 'For…Next'-Schleife ohne ausführbare Anweisungen lässt andere Entwickler über die Absicht des Codes im unklaren. Vermeiden Sie das Schreiben von unnötigem Code.
+
+ Ein leerer 'Else'-Block ohne ausführbare Anweisungen lässt andere Entwickler über die Absicht des Codes im unklaren. Vermeiden Sie das Schreiben von unnötigem Code.
-
- Zwei Deklarationen sind aktiv und haben denselben Namen. Dies bedeutet, dass nur eine von ihnen zur Verwendung verfügbar ist.
+
+ Der größte Wert einer vorzeichenbehafteten 16-bit Ganzzahl ist 32.767 - Eine 32-bit Ganzzahl (Long) zu verwenden, wo es möglich ist, kann Überlauffehler zur Laufzeit verhindern und ist für moderne CPUs einfacher.Das Schlüsselwort 'Stop' unterbricht die Ausführung und ruft den Debugger auf. Vermeiden Sie die Verwendung in verteiltem Code.
@@ -274,30 +277,33 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
Ein leerer 'Case'-Block ohne ausführbare Anweisungen lässt andere Entwickler über die Absicht des Codes im unklaren. Vermeiden Sie das Schreiben von unnötigem Code.
+
+ Eine leere 'Do…While'-Schleife ohne ausführbare Anweisungen lässt andere Entwickler über die Absicht des Codes im unklaren. Vermeiden Sie das Schreiben von unnötigem Code.
+
Eine leere 'For Each…Next'-Schleife ohne ausführbare Anweisungen lässt andere Entwickler über die Absicht des Codes im unklaren. Vermeiden Sie das Schreiben von unnötigem Code.
-
- Ein leerer 'Else'-Block ohne ausführbare Anweisungen lässt andere Entwickler über die Absicht des Codes im unklaren. Vermeiden Sie das Schreiben von unnötigem Code.
+
+ Eine leere 'For…Next'-Schleife ohne ausführbare Anweisungen lässt andere Entwickler über die Absicht des Codes im unklaren. Vermeiden Sie das Schreiben von unnötigem Code.Eine leere 'While…Wend'-Schleife ohne ausführbare Anweisungen lässt andere Entwickler über die Absicht des Codes im unklaren. Vermeiden Sie das Schreiben von unnötigem Code.
+
+ Zwei Deklarationen sind aktiv und haben denselben Namen. Dies bedeutet, dass nur eine von ihnen zur Verwendung verfügbar ist.
+
Die 'Error'-Anweisung existiert in der Sprache nur um Legacy-Programme zu unterstützen, die sie benötigten; Bevorzugen Sie stattdessen 'Err.Raise'.
-
- Der größte Wert einer vorzeichenbehafteten 16-bit Ganzzahl ist 32.767 - Eine 32-bit Ganzzahl (Long) zu verwenden, wo es möglich ist, kann Überlauffehler zur Laufzeit verhindern und ist für moderne CPUs einfacher.
-
-
- Eine leere 'Do…While'-Schleife ohne ausführbare Anweisungen lässt andere Entwickler über die Absicht des Codes im unklaren. Vermeiden Sie das Schreiben von unnötigem Code.
-
Ein Element wird in verschiedenen Zweigen einer if-Anweisung mit True / False zugewiesen, wobei keine anderen Anweisungen in der Bedingung enthalten sind. Verwenden Sie die Bedingung stattdessen direkt (als Zuweisung) für das Element.Leere Module und Klassen weisen entweder auf noch nicht implementierte Funktionalitäten hin oder stellen unnötigen Ballast dar, der die Wartbarkeit eines Projekts behindern kann.
+
+ Eine Bedingung in einem Case-Ausdruck ist entweder nie erfüllt, verursacht einen Laufzeitfehler oder kann nicht erfüllt werden, da die vorherigen Case-Ausdrücke bereits alle zulässigen Werte abdecken. Infolgedessen wird der Code in dem Case-Zweig nie ausgeführt und stellt "toten Code" dar oder der Case-Ausdruck stellt sogar einen Laufzeitfehler dar, der nur darauf wartet irgendwann aufzutreten. Der Case-Zweig sollte entweder gelöscht, verändert oder an eine andere Stelle verschoben werden.
+
Fehlerbehandlung sollte nach Verwendung von 'On Error Resume Next' wiederhergestellt werden.
@@ -376,15 +382,15 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
Der VBA-Compiler gibt keinen Fehler aus, wenn ein Objekt einer Variables Set-zugewiesen wird mit einem inkompatiblen Objekttype, d.h. deren Typ weder identisch, ein Subtyp noch ein Supertyp ist. In fast allen Fällen führt dies zu einem Laufzeitfehler, der schwerer zu entdecken ist und auf einen Programmierfehler hinweist. In allen anderen Fällen kann der Quallcode so geändert werden, dass er ausschließlich Zuweisungen zwischen kompatiblen deklarierten Typen verwendet.
-
- Der VBA-Compiler gibt keinen Fehler aus, wenn ein Objekt als Argument für einen Parameter mit einem inkompatiblen Objekttyp übergeben wird, d.h. dessen Typ weder identisch, ein Subtyp, noch ein Supertyp ist. In fast allen Fällen führt dies zu einem Laufzeitfehler, der schwer zu entdecken ist und auf einen Programmierfehler hinweist. In allen anderen Fällen kann der Quellcode so geändert werden, dass ausschließlich Argumente mit kompatiblen deklarierten Typen verwendet werden.
-
Methoden ohne ausführbare Anweisungen können den Eindruck erwecken, dass sie etwas tun, was sie eigentlich nicht tun. Dies kann zu unerwartetem Verhalten führen.Eine Klasse, die dafür gedacht ist von anderen Klassen als Interface genutzt zu werden, sollte gewöhnlicher Weise keine Implementierungen enthalten. Falls die Intention ist diese Klasse direkt als konkrete Klasse zu verwenden, kann dieses Inspektionsresultat ignoriert werden.
+
+ Der VBA-Compiler gibt keinen Fehler aus, wenn ein Objekt als Argument für einen Parameter mit einem inkompatiblen Objekttyp übergeben wird, d.h. dessen Typ weder identisch, ein Subtyp, noch ein Supertyp ist. In fast allen Fällen führt dies zu einem Laufzeitfehler, der schwer zu entdecken ist und auf einen Programmierfehler hinweist. In allen anderen Fällen kann der Quellcode so geändert werden, dass ausschließlich Argumente mit kompatiblen deklarierten Typen verwendet werden.
+
Der VBA-Compiler gibt keinen Fehler aus, wenn ein Objekt an einer Stelle verwendet wird, die einen Wert verlangt, und der deklarierte Type des Objekts keinen passendes Standardelement hat. In fast allen Fällen führt dies zu einem Laufzeitfehler 91 'Objektvariable oder With-Blockvariable nicht festgelegt' oder 438 'Objekt unterstützt diese Eigenschaft oder Methode nicht' abhängig davon, ob die Variable den Wert 'Nothing' hat oder nicht, der schwerer zu entdecken ist und auf einen Programmierfehler hinweist.
@@ -427,9 +433,6 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
Wenn beide Seiten einer Zuweisung ohne Set Objekte sind, kommt es zu einer Zuweisung vom Standardelement der rechten Seite zu dem der linken. Auch wenn dies manchmal beabsichtigt sein kann, verschleiert es meistens, dass Set fehlerhafter Weise vergessen wurde.
-
- Eine Bedingung in einem Case-Ausdruck ist entweder nie erfüllt, verursacht einen Laufzeitfehler oder kann nicht erfüllt werden, da die vorherigen Case-Ausdrücke bereits alle zulässigen Werte abdecken. Infolgedessen wird der Code in dem Case-Zweig nie ausgeführt und stellt "toten Code" dar oder der Case-Ausdruck stellt sogar einen Laufzeitfehler dar, der nur darauf wartet irgendwann aufzutreten. Der Case-Zweig sollte entweder gelöscht, verändert oder an eine andere Stelle verschoben werden.
-
Der Rückgabewert einer Funktion wird verworfen, d.h. die Funktion wird wie eine Prozedur verwendet. Dies ist entweder ein Versäumnis oder die Funktion wird wegen ihrer Nebenwirkungen verwendet, deren Existenz in der Regel selber problematisch wäre.
@@ -448,34 +451,31 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
Der letzte Parameter (der 'Wert'-Parameter) der Eigenschaftsmutation wird immer als ByVal übergeben. Dies gilt unabhänig der An- oder Abwesenheit eines ByRef oder ByVal Modifizieres. Ausnahme: Ein nutzerdefinierter Type (UserDefinedType) muss immer als ByRef übergeben werden, auch wenn er der letzte Parameter einer Eigenschaftmutation ist.
-
- Ein Kommentar wurde als eine syntaktisch zulässige Annotation erkannt, doch kein unterstützter Annotationstyp konnte erkannt werden.
-
Eine Annotation wurde in einer Komponente mit einem zu dieser inkompatiblen Typ verwendet. Manche Annotationen können nur in Komponenten eines spezifischen Typs verwendet werden, andere wiederum nicht in Komponenten bestimmter Typen.
-
- Die Annotation konnte keinem Ziel zugewiesen werden. Eine Annotation für die Modulebene kann nicht verwendet werden, um Elemente zu annotieren. Eine Annotation für Elemente kann auf Modulebene nicht verwendet werden. Modul- und Elementannotationen sollten nur einmal spezifiziert werden.
+
+ Ein Kommentar wurde als eine syntaktisch zulässige Annotation erkannt, doch kein unterstützter Annotationstyp konnte erkannt werden.
-
- Ein UDT (User Defined Type) Element ist deklariert, das allerdings nicht verwendet wird. Es sollte überlegt werden, die Deklaration des UDT Elementes zu löschen.
+
+ Alle Argumente eines Funktions-/Prozeduraufrufes werden immer evaluiert, bevor die Funktion aufgerufen wird, so dass ihre Werte als Parameter übergeben werden. Allerdings führt die 'IIf'-Funktion manchmal zu einer Fehlinterpretation, dass entweder nur der 'Wahr-Teil' oder nur der 'Falsch-Teil' auf der Basis des ersten Argumentes ausgewertet wird. Somit kann die 'IIf'-Funktion eine Quelle von unvorhergesehen Nebeneffekten und Fehlern sein, wenn der Nutzer den Umstand nicht vor Augen hat, dass immer beide Argumente, 'Wahr-Teil' und 'Falsch-Teil', ausgewertet werden.
-
- Das Standard (Public) Interface einer Modul-Klasse sollte nicht die Implementierung anderer Interfaces oder Ereignishandler offenlegen.
+
+ Normalerweise fängt der VBE Editor diesen Fehlertyp und bricht das Kompilieren ab. Allerdings gibt es einige wenige Szenarien, in denen dieser Fehler übergangen und ein Laufzeitfehler ausgelöst wird. Um den Laufzeitfehler zu vermeiden, sollte die fehlende Property oder Subroutine implementiert werden.
-
- Das Kopieren eines Arbeitsblattes, das eine öffentliche Enumerationsdeklartion enthält, wird auch eine Kopie der Enumerationsdeklaration anlegen. Diese Kopie wird einen 'Ambiguous name detected'-Kompiler-Fehler auslösen. Die Deklaration von Enumerationen in Standard- oder Klassenmodulen vermeidet ungewollte Duplikate einer Enumerationsdeklaration.
+
+ Obwohl eine zustandsorientierte (stateful) Standardinstanz eventuell gewünscht ist, ist diese eine beliebte Quelle von Fehlern und sollte vermieden werden. Nutze die 'Me'-Auszeichnung, um die aktuelle Instanz explizit anzusprechen und Zweideutigkeiten zu vermeiden.MS Forms legt UserForms-Steuerelemente als öffentliche Felder an. Der Zugriff auf diese Felder außerhalb der UserForm-Klasse bricht die Kapselung und verursacht unnötigen Code mit speziellen Formularsteuerelementen. Überlege, die gewünschten Werte in eigene 'Modell-Klassen' zu kapseln und Ereignishandler innerhalb des Formulars zu verwenden, um diese 'Modelleigenschaften' zu ändern. Der Code kann dann die gekapselten Werte anfragen anstatt der Formularsteuerelemente.
-
- Obwohl eine zustandsorientierte (stateful) Standardinstanz eventuell gewünscht ist, ist diese eine beliebte Quelle von Fehlern und sollte vermieden werden. Nutze die 'Me'-Auszeichnung, um die aktuelle Instanz explizit anzusprechen und Zweideutigkeiten zu vermeiden.
+
+ Das Kopieren eines Arbeitsblattes, das eine öffentliche Enumerationsdeklartion enthält, wird auch eine Kopie der Enumerationsdeklaration anlegen. Diese Kopie wird einen 'Ambiguous name detected'-Kompiler-Fehler auslösen. Die Deklaration von Enumerationen in Standard- oder Klassenmodulen vermeidet ungewollte Duplikate einer Enumerationsdeklaration.
-
- Normalerweise fängt der VBE Editor diesen Fehlertyp und bricht das Kompilieren ab. Allerdings gibt es einige wenige Szenarien, in denen dieser Fehler übergangen und ein Laufzeitfehler ausgelöst wird. Um den Laufzeitfehler zu vermeiden, sollte die fehlende Property oder Subroutine implementiert werden.
+
+ Ein UDT (User Defined Type) Element ist deklariert, das allerdings nicht verwendet wird. Es sollte überlegt werden, die Deklaration des UDT Elementes zu löschen.
-
- Alle Argumente eines Funktions-/Prozeduraufrufes werden immer evaluiert, bevor die Funktion aufgerufen wird, so dass ihre Werte als Parameter übergeben werden. Allerdings führt die 'IIf'-Funktion manchmal zu einer Fehlinterpretation, dass entweder nur der 'Wahr-Teil' oder nur der 'Falsch-Teil' auf der Basis des ersten Argumentes ausgewertet wird. Somit kann die 'IIf'-Funktion eine Quelle von unvorhergesehen Nebeneffekten und Fehlern sein, wenn der Nutzer den Umstand nicht vor Augen hat, dass immer beide Argumente, 'Wahr-Teil' und 'Falsch-Teil', ausgewertet werden.
+
+ Das Standard (Public) Interface einer Modul-Klasse sollte nicht die Implementierung anderer Interfaces oder Ereignishandler offenlegen.
\ No newline at end of file
diff --git a/Rubberduck.Resources/Inspections/InspectionInfo.es.resx b/Rubberduck.Resources/Inspections/InspectionInfo.es.resx
index 969345fe51..ba9737f86b 100644
--- a/Rubberduck.Resources/Inspections/InspectionInfo.es.resx
+++ b/Rubberduck.Resources/Inspections/InspectionInfo.es.resx
@@ -217,6 +217,9 @@ Si el parámetro puede ser nulo, ignore el resultado de esta inspección; pasar
Una declaración de variable de objeto auto-instanciada en el ámbito del procedimiento cambia cómo funciona la anulación de la referencia, lo que puede llevar a un comportamiento inesperado.
+
+ Un miembro se escribe como función, pero siempre se usa como procedimiento. Considere convertir la 'Function' en un 'Sub'.
+
Por lo que Rubberduck puede decir, esta variable es una variable de objeto, asignada sin la palabra clave 'Set'. Esto causa el error 91 en tiempo de ejecución 'Objeto o variable de bloque no establecida'.
@@ -295,6 +298,9 @@ Si el parámetro puede ser nulo, ignore el resultado de esta inspección; pasar
Los módulos y clases vacíos apuntan a una funcionalidad aún no implementada o representan un equipaje innecesario que puede perjudicar la mantenibilidad de un proyecto.
+
+ Una condición del 'Case' siempre se evalúa como False, causa un error de tiempo de ejecución o el efecto acumulativo de las sentencias del 'Case' anteriores representa todos los valores posibles o un superconjunto de los valores de la sentencia del 'Case'. Como resultado, el bloque 'Case' nunca se ejecutará y es un "código muerto", o la instrucción 'Case' es un error de tiempo de ejecución esperando a suceder. Considere eliminar, reordenar o modificar la sentencia 'Case'.
+
El manejo de errores se debe restaurar después de usar 'On Error Resume Next'.
@@ -367,21 +373,21 @@ Si el parámetro puede ser nulo, ignore el resultado de esta inspección; pasar
Si bien esto es legal, se trata de una "característica" mal documentada que significa algo diferente: el estado de error también se borra además de deshabilitar cualquier manejo de errores. Sin embargo, esto puede ser ambiguo, ya que una etiqueta de línea negativa de -1 puede terminar como un objetivo y un manejo de errores excesivamente complejo generalmente indica la necesidad de refactorizar el procedimiento.
-
- El compilador VBA no arroja un error si un objeto se pasa como argumento para un parámetro declarado como tipo objeto y el mismo resulta incompatible, por ejemplo. con un objeto que no es del mismo tipo que el parámetro declarado, ni es supertipo ni tampoco subtipo. En la mayoría de los casos pasar un argumento así conduce a un error en tiempo de ejecución, el cual es más difícil de detectar y se considera un bug. En el resto de las situaciones, el código se puede cambiar para que solamente se usen argumentos de tipos declarados compatibles.
-
-
- Un miembro se escribe como función, pero siempre se usa como procedimiento. Considere convertir la 'Function' en un 'Sub'.
-
-
- Una condición del 'Case' siempre se evalúa como False, causa un error de tiempo de ejecución o el efecto acumulativo de las sentencias del 'Case' anteriores representa todos los valores posibles o un superconjunto de los valores de la sentencia del 'Case'. Como resultado, el bloque 'Case' nunca se ejecutará y es un "código muerto", o la instrucción 'Case' es un error de tiempo de ejecución esperando a suceder. Considere eliminar, reordenar o modificar la sentencia 'Case'.
-
Los bucles 'While ... Wend' existen por compatibilidad con versiones anteriores pero han sido reemplazados por la introducción de los bloques 'Do While ... Loop', que admiten la sentencia de salida 'Exit Do'. Los ciclos 'While ... Wend' no pueden salir más allá del cumplimiento de la condición 'While'.El compilador VBA no arroja un error si un objeto se asigna a una variable con un tipo de objeto declarado incompatible, por ejemplo, con un objeto que no es del mismo tipo que el parámetro declarado, ni es supertipo ni tampoco subtipo. En la mayoría de los casos, dicha asignación conduce a un error en tiempo de ejecución, el cual es más difícil de detectar e indica un bug. En todas las demás situaciones, el código se puede cambiar para usar solo asignaciones entre tipos declarados compatibles.
+
+ Los métodos sin sentencias ejecutables pueden aparentemente hacer algo que realmente no hacen y, por lo tanto, causan un comportamiento inesperado.
+
+
+ Un módulo de clase que se utilizará como interfaz para clases concretas generalmente debe abstraerse de cualquier implementación. Si tiene la intención de utilizar este módulo de clase como un tipo concreto, puede ignorar este resultado de inspección de forma segura.
+
+
+ El compilador VBA no arroja un error si un objeto se pasa como argumento para un parámetro declarado como tipo objeto y el mismo resulta incompatible, por ejemplo. con un objeto que no es del mismo tipo que el parámetro declarado, ni es supertipo ni tampoco subtipo. En la mayoría de los casos pasar un argumento así conduce a un error en tiempo de ejecución, el cual es más difícil de detectar y se considera un bug. En el resto de las situaciones, el código se puede cambiar para que solamente se usen argumentos de tipos declarados compatibles.
+
El compilador VBA no arroja un error si se usa un objeto en un lugar que requiere un tipo de valor y el tipo declarado del objeto no posee un miembro default adecuado. En la mayoría de los casos, esto ocasiona un error 91 en tiempo de ejecución 'Object or With block variable not set' o un error 438 'Object doesn't support this property or method' dependiendo de si el objeto tiene o no el valor 'Nothing', lo cual es díficil de detectar e indica un bug.
@@ -391,12 +397,6 @@ Si el parámetro puede ser nulo, ignore el resultado de esta inspección; pasar
El compilador VBA no arroja un error si se requiere un miembro default indexado y el tipo declarado del objeto no posee un miembro default adecuado. En la mayoría de los casos, esto conduce a un error 91 en tiempo de ejecución 'Object or With block variable not set' o un error 438 'Object doesn't support this property or method' dependiendo de si el objeto tiene o no el valor 'Nothing', lo cual es díficil de detectar e indica un bug.
-
- Los métodos sin sentencias ejecutables pueden aparentemente hacer algo que realmente no hacen y, por lo tanto, causan un comportamiento inesperado.
-
-
- Un módulo de clase que se utilizará como interfaz para clases concretas generalmente debe abstraerse de cualquier implementación. Si tiene la intención de utilizar este módulo de clase como un tipo concreto, puede ignorar este resultado de inspección de forma segura.
-
La notación Bang, formalmente conocida como expresión de acceso al diccionario, parece estar fuertemente tipada. Sin embargo, en realidad es un acceso de tipo secuencial al miembro default parametrizado del objeto en el que se usa.
@@ -409,34 +409,34 @@ Si el parámetro puede ser nulo, ignore el resultado de esta inspección; pasar
Usar un objeto con un miembro default en un lugar que requiere un procedure conduce a una invocación implícita del miembro default. Esto es probablemente no intencional y afecta negativamente la legibilidad.
-
- Una anotación tiene más argumentos que los permitidos, se ignoran los argumentos sobrantes.
+
+ Un acceso de miembro default oculta a qué miembro se llama realmente. Aunque es evidente que se realiza alguna llamada en el caso de que un acceso de miembro default indexado sea explícito, generalmente es mejor para la legibilidad.
-
- Siempre que ambos lados de una asignación sin Set sean objetos, hay una asignación del miembro default del de la derecha al miembro de la izquierda. Aunque esto puede ser intencional, en muchas situaciones solo enmascarará un Set olvidado por error.
+
+ Un acceso de miembro default oculta a qué miembro se llama realmente. Aunque es evidente que se realiza alguna llamada en el caso de que un acceso de miembro default indexado sea explícito, generalmente es mejor para la legibilidad. Esto se aplica especialmente si el miembro default al que se accede no está en la interfaz del objeto en sí, sino que debe resolverse mediante una cadena de llamadas de miembros default.
-
- El valor de retorno de una función resulta descartado, por ejemplo. si la función se usa como un procedimiento. Esto es un descuido o la función se usa para sus efectos secundarios, cuya existencia también sería un Code Smell.
+
+ Un acceso de miembro default oculta a qué miembro se llama realmente. Aunque es evidente que se realiza alguna llamada en el caso de que un acceso de miembro default indexado sea explícito, generalmente es mejor para la legibilidad. Esto es especialmente cierto si el miembro default no se puede determinar en tiempo de compilación. Además, si no hubiera un miembro default adecuado en tiempo de ejecución, se generará un error 438 'Object doesn't support this property or method'.Los accesos de miembros default ocultan el miembro realmente llamado. Esto es especialmente confuso si no hay indicación en la expresión de que se realice tal llamada. Puede causar que los errores en los que se olvidó llamar a un miembro pasen desapercibidos.
-
- Si no se incluye la cláusula As type para un Const, se escribe implícitamente. Incluya un 'As <Type>' explícito que reemplace '<Type>' con el tipo de datos correcto para declarar explícitamente su constante.
-
Los accesos de miembros default ocultan el miembro realmente llamado. Esto es especialmente confuso si no hay indicación en la expresión de que se realiza una llamada de este tipo y el miembro default final no está en la interfaz del objeto en sí. En particular, esto puede causar que los errores en los que se olvidó llamar a un miembro pasen desapercibidos.Los accesos de miembros default ocultan el miembro realmente llamado. Esto es especialmente confuso si no hay indicación en la expresión de que se realiza una llamada de este tipo y si el miembro default no se puede determinar a partir del tipo declarado del objeto. Como consecuencia, los errores en los que se olvidó llamar a un miembro pueden pasar desapercibidos y si no hay un miembro default adecuado en tiempo de ejecución, se generará un error 438 'El objeto no admite esta propiedad o método'.
-
- Un acceso de miembro default oculta a qué miembro se llama realmente. Aunque es evidente que se realiza alguna llamada en el caso de que un acceso de miembro default indexado sea explícito, generalmente es mejor para la legibilidad.
+
+ Siempre que ambos lados de una asignación sin Set sean objetos, hay una asignación del miembro default del de la derecha al miembro de la izquierda. Aunque esto puede ser intencional, en muchas situaciones solo enmascarará un Set olvidado por error.
-
- Un acceso de miembro default oculta a qué miembro se llama realmente. Aunque es evidente que se realiza alguna llamada en el caso de que un acceso de miembro default indexado sea explícito, generalmente es mejor para la legibilidad. Esto se aplica especialmente si el miembro default al que se accede no está en la interfaz del objeto en sí, sino que debe resolverse mediante una cadena de llamadas de miembros default.
+
+ El valor de retorno de una función resulta descartado, por ejemplo. si la función se usa como un procedimiento. Esto es un descuido o la función se usa para sus efectos secundarios, cuya existencia también sería un Code Smell.
-
- Un acceso de miembro default oculta a qué miembro se llama realmente. Aunque es evidente que se realiza alguna llamada en el caso de que un acceso de miembro default indexado sea explícito, generalmente es mejor para la legibilidad. Esto es especialmente cierto si el miembro default no se puede determinar en tiempo de compilación. Además, si no hubiera un miembro default adecuado en tiempo de ejecución, se generará un error 438 'Object doesn't support this property or method'.
+
+ Si no se incluye la cláusula As type para un Const, se escribe implícitamente. Incluya un 'As <Type>' explícito que reemplace '<Type>' con el tipo de datos correcto para declarar explícitamente su constante.
+
+
+ Una anotación tiene más argumentos que los permitidos, se ignoran los argumentos sobrantes.
\ No newline at end of file
diff --git a/Rubberduck.Resources/Inspections/InspectionInfo.fr.resx b/Rubberduck.Resources/Inspections/InspectionInfo.fr.resx
index 7d9a49e503..606f1dee78 100644
--- a/Rubberduck.Resources/Inspections/InspectionInfo.fr.resx
+++ b/Rubberduck.Resources/Inspections/InspectionInfo.fr.resx
@@ -138,6 +138,9 @@
Les références implicites au classeur actif rendent le code plus fragile et plus difficile à déboguer. Considérez rendre ces références explicites lorsqu'elles sont intentionelles, et préférez l'utilisations de références d'objets. Ignorez ce résultat si l'appel réfère à un type que Rubberduck n'a pu résoudre.
+
+ Les paramètres sont passés par référence à moins d'avis contraire explicite, ce qui peut être confondant et fragiliser le code. Préférez passer les paramètres par valeur, et spécifiez 'ByRef' explicitement quand des paramètres doivent être passés par référence.
+
Les membres d'un module sont publics par défaut, ce qui peut être contre-intuitif. Considérez spécifier les modificateurs d'accès explicitement pour éviter toute ambiguïté.
@@ -189,6 +192,10 @@
Probablement un bogue: une variable est utilisée avant d'être assignée.
+
+ Une fonction équivalente retourne une valeur 'String' et devrait préférablement être utilisée afin d'éviter les conversions implicites.
+Si le paramètre peut être nul, ignorer ce résultat; passer une valeur nulle à cette fonction causerait une erreur d'exécution 'type mismatch'.
+
Les identifiants devrait indiquer ce pour quoi ils sont utilisés, devraient être lisibles; évitez de suprimer les voyelles, évitez les suffixes numériques, et les noms de 1-2 caractères.
@@ -210,12 +217,14 @@
Une variable objet assignée lors de sa déclaration dans une procédure, modifie comment VBA gère cet objet, ce qui peut mener à un comportement inattendu.
+
+ Un membre est défini comme étant une fonction, mais son utilisation ne diffère en rien d'une procédure 'Sub' standard. Considérez convertir cette function en procédure.
+
Rubberduck voit cette variable comme étant une référence à un objet, assignée sans le mot-clé 'Set'. Ceci cause une erreur d'exécution (#91 'Object or With block variable not set').
-
- Une fonction équivalente retourne une valeur 'String' et devrait préférablement être utilisée afin d'éviter les conversions implicites.
-Si le paramètre peut être nul, ignorer ce résultat; passer une valeur nulle à cette fonction causerait une erreur d'exécution 'type mismatch'.
+
+ Un paramètre d'annotation est manquant ou incorrectement spécifié. La syntaxe correcte est: '@Annotation([paramètre])\nExemple: '@Folder("Parent.Enfant")Le mot-clé 'Public' peut seulement être utilisé au niveau module; son contraire 'Private' est également seulement permis au niveau module. Toutefois, 'Dim' peut être utilisé autant pour déclarer une variable locale qu'une variable module. Pour fins de constance, il est donc préférable de réserver le mot-clé 'Dim' pour les variables locales, et d'utiliser 'Private' au lieu de 'Dim' au niveau module.
@@ -223,78 +232,78 @@ Si le paramètre peut être nul, ignorer ce résultat; passer une valeur nulle
Un module utilisant des variables non déclarées ne peut pas être compilé si Option Explicit est présent. Les variables non déclarées sont toujours Variant, un type qui occupe plus d'espace et requiert plus de traitement que nécessaire.
-
- Un paramètre d'annotation est manquant ou incorrectement spécifié. La syntaxe correcte est: '@Annotation([paramètre])\nExemple: '@Folder("Parent.Enfant")
+
+ La notation hongroise rend le code plus difficile à lire, et est redondante lorsque les variables ont un type explicite et que des identifiants éloquents sont utilisés.Un membre est accédé mais ne semble pas exister dans l'interface de l'objet. Ceci causera probablement une erreur d'exécution #438.
-
- La notation hongroise rend le code plus difficile à lire, et est redondante lorsque les variables ont un type explicite et que des identifiants éloquents sont utilisés.
+
+ L'expression est évaluée par l'application hôte au moment de l'exécution, ce qui implique que VBA ne peut valider l'expression lors de la compilation. Considérez utiliser plutôt le modèle d'objet de l'application hôte.L'objet Excel Application n'implémente pas l'interface WorksheetFunction directement; les appels de fonctions WorksheetFunction effectués sur Application, renvoie une valeur VbVarType.Error; ces erreurs ne peuvent être capturées avec la gestion d'erreurs de VBA et encourent une pénalité de performance par rapport à un appel équivalent de WorksheetFunction. Note: assurez-vous de gérer les erreurs d'exécution en appliquant ce correctif.
-
- L'expression est évaluée par l'application hôte au moment de l'exécution, ce qui implique que VBA ne peut valider l'expression lors de la compilation. Considérez utiliser plutôt le modèle d'objet de l'application hôte.
+
+ Comme il s'agit du comportement par défaut, nul besoin de le spécifier.
-
- Une boucle 'For...Next' vide, qui ne contient aucune instruction exécutable, laisse songeur quant aux intentions de l'auteur. Évitez d'écrire du code qui n'a pas besoin d'être écrit.
+
+ L'annotation n'a pu être liée à une cible. Une annotation ciblant un module ne peut être utilisée pour une méthode; une annotation destinée à un membre ne peut être utilisée pour un module.
-
- Deux déclarations ont le même nom dans le même espace-nom: une seule d'entre elles peut être utilisée.
+
+ Une annotation Rubberduck est spécifiée pour un module ou un membre, mais l'attribut correspondant n'est pas présent. Les attributs et annotations du module doivent être synchronisés.
+
+
+ Une branche conditionelle vide, qui ne contient aucune instruction exécutable, laisse songeur quant aux intentions de l'auteur. Évitez d'écrire du code qui n'a pas besoin d'être écrit.Cette instruction correspondant aux paramètres par défaut et peut être supprimée sans effet.
-
- Le mot-clé 'Stop' halte l'exécution et ouvre l'éditeur VBA; évitez de livrer du code qui l'utilise.
-
-
- Un bloc 'Case' vide, qui ne contient aucune instruction exécutable, laisse songeur quant aux intentions de l'auteur. Évitez d'écrire du code qui n'a pas besoin d'être écrit.
+
+ Les paramètres sont passés par référence par défaut; il n'est donc pas nécessaire d'inclure le modificateur 'ByRef'.
-
- Une boucle 'Loop' vide, qui ne contient aucune instruction exécutable, laisse songeur quant aux intentions de l'auteur. Évitez d'écrire du code qui n'a pas besoin d'être écrit.
+
+ Une étiquette de ligne qui n'est pas utilisée ('GoTo', 'Resume', ...), n'a pas d'utilité. Considerez les supprimer.Un block 'Else' vide, qui ne contient aucune instruction exécutable, laisse songeur quant aux intentions de l'auteur. Évitez d'écrire du code qui n'a pas besoin d'être écrit.
-
- Les paramètres sont passés par référence par défaut; il n'est donc pas nécessaire d'inclure le modificateur 'ByRef'.
+
+ La valeur maximale d'un nombre entier 16-bits signé est de 32,767 - utiliser un entier 32-bit (Long) où c'est possible, aide à prévenir certaines erreurs 'Overflow'. Les processurs modernes travaillent aussi plus efficacement avec des entiers 32-bits.
-
- Comme il s'agit du comportement par défaut, nul besoin de le spécifier.
+
+ Le mot-clé 'Stop' halte l'exécution et ouvre l'éditeur VBA; évitez de livrer du code qui l'utilise.
-
- Les paramètres sont passés par référence à moins d'avis contraire explicite, ce qui peut être confondant et fragiliser le code. Préférez passer les paramètres par valeur, et spécifiez 'ByRef' explicitement quand des paramètres doivent être passés par référence.
+
+ Un bloc 'Case' vide, qui ne contient aucune instruction exécutable, laisse songeur quant aux intentions de l'auteur. Évitez d'écrire du code qui n'a pas besoin d'être écrit.
-
- Une annotation Rubberduck est spécifiée pour un module ou un membre, mais l'attribut correspondant n'est pas présent. Les attributs et annotations du module doivent être synchronisés.
+
+ Un bloc 'Loop' vide, qui ne contient aucune instruction exécutable, laisse songeur quant aux intentions de l'auteur. Évitez d'écrire du code qui n'a pas besoin d'être écrit.
-
- Une branche conditionelle vide, qui ne contient aucune instruction exécutable, laisse songeur quant aux intentions de l'auteur. Évitez d'écrire du code qui n'a pas besoin d'être écrit.
+
+ Une boucle 'Loop' vide, qui ne contient aucune instruction exécutable, laisse songeur quant aux intentions de l'auteur. Évitez d'écrire du code qui n'a pas besoin d'être écrit.
+
+
+ Une boucle 'For...Next' vide, qui ne contient aucune instruction exécutable, laisse songeur quant aux intentions de l'auteur. Évitez d'écrire du code qui n'a pas besoin d'être écrit.Une boucle 'Loop' vide, qui ne contient aucune instruction exécutable, laisse songeur quant aux intentions de l'auteur. Évitez d'écrire du code qui n'a pas besoin d'être écrit.
+
+ Deux déclarations ont le même nom dans le même espace-nom: une seule d'entre elles peut être utilisée.
+
L'instruction 'Error' n'existe que pour permettre au code plus ancien de pouvoir s'exécuter; 'Error' peut être remplacé par 'Err.Raise'.
-
- La valeur maximale d'un nombre entier 16-bits signé est de 32,767 - utiliser un entier 32-bit (Long) où c'est possible, aide à prévenir certaines erreurs 'Overflow'. Les processurs modernes travaillent aussi plus efficacement avec des entiers 32-bits.
-
-
- Une étiquette de ligne qui n'est pas utilisée ('GoTo', 'Resume', ...), n'a pas d'utilité. Considerez les supprimer.
-
-
- Un bloc 'Loop' vide, qui ne contient aucune instruction exécutable, laisse songeur quant aux intentions de l'auteur. Évitez d'écrire du code qui n'a pas besoin d'être écrit.
-
Une valeur Booléenne est assignée dans des branches conditionelles qui ne comportent aucune autre instruction. Remplacez la condition par une assignation directe.Les modules et classes vides démontrent des fonctionnalités pas encore implémentées ou représentent un fardeau non nécessaire pouvant nuire à la maintenance du projet.
+
+ Une condition est toujours fausse, cause une erreur d'exécution, ou les effets cumulatifs de conditions précédentes représentent toutes les valeurs possibles, bref la condition a déjà été évaluée et ce bloc 'Case' est effectivement inatteignable.
+
La gestion d'erreurs devrait être restaurée après l'utilisation de 'On Error Resume Next'.
@@ -316,17 +325,14 @@ Si le paramètre peut être nul, ignorer ce résultat; passer une valeur nulle
Visual Basic sous Windows supporte uniquement la convention d'appel StdCall. La convention CDecl n'est supportée seulement que sur Macintosh. L'utilisation de ce mot-clé sous Windows causera l'erreur d'exécution 49 "Bad DLL calling convention". Utiliser un bloc de compilation conditionelle si cette procédure doit s'exécuter sur un Mac.
-
- Une assignation est écrasée par une assignation subséquente, ou la valeur assignée n'est jamais utilisée.
-
Une annotation à usage unique ne peut être spécifiée à plus d'un endroit dans un module.
-
- Une procédure qui renvoie une référence à un objet peut renvoyer une référence nulle 'Nothing'. Ceci causerait l'erreur d'exécution 91 "Object variable or With block variable not set".
+
+ Les modules sans annotation '@Folder' ne peuvent être regroupés dans l'Explorateur de Code.
-
- Les fonctions qui sont visibles en tant que fonctions définies par l'utilisateur dans Excel, renverront une erreur '#REF!' lorsqu'utilisées dans une feuille de calcul si leur nom correspond à une référence de cellule valide. Si la fonction doit être utilisée comme fonction définie par l'utilisateur, elle doit être renommée. Sinon, sa visibilité devrait être réduite à 'Private', ou alors la fonction doit être déplacée vers un autre type de module.
+
+ 'On Local Error' subsiste pour fins de compatibilité avec d'anciennes versions de Visual Basic; toutes les erreurs sont locales. Utiliser ce mot-clé peut donner la fausse impression que plusieurs types d'erreurs et/ou de gestion d'erreurs existent, ce qui n'est pas le cas.'IsMissing' ne doit être utilisé qu'avec un paramètre optionnel, et ne renverra de résultats corrects que si le type du paramètre est 'Variant'. Pour tout autre type, la fonction retournera 'False'.
@@ -334,15 +340,18 @@ Si le paramètre peut être nul, ignorer ce résultat; passer une valeur nulle
'IsMissing' ne doit être utilisée qu'avec les paramètres de la procédure, tout autre usage renverra la valeur constante 'False'. Passer toute autre expression à cette fonction est l'équivalent de 'VarType({expression}) = vbError', ce qui dans de rares circonstances peut faire planter l'application hôte.
-
- Les modules sans annotation '@Folder' ne peuvent être regroupés dans l'Explorateur de Code.
-
-
- 'On Local Error' subsiste pour fins de compatibilité avec d'anciennes versions de Visual Basic; toutes les erreurs sont locales. Utiliser ce mot-clé peut donner la fausse impression que plusieurs types d'erreurs et/ou de gestion d'erreurs existent, ce qui n'est pas le cas.
+
+ Une assignation est écrasée par une assignation subséquente, ou la valeur assignée n'est jamais utilisée.Un module de classe qui contient un ou des membres dont le nom comporte un caractère de soulignement, ne peut être implémenté par d'autres classes. Ce caractère est utilisé par Visual Basic pour séparer le nom d'une interface et celui d'un membre de cette interface; la compilation échouera si le membre contient un caractère de soulignement.
+
+ Une procédure qui renvoie une référence à un objet peut renvoyer une référence nulle 'Nothing'. Ceci causerait l'erreur d'exécution 91 "Object variable or With block variable not set".
+
+
+ Les fonctions qui sont visibles en tant que fonctions définies par l'utilisateur dans Excel, renverront une erreur '#REF!' lorsqu'utilisées dans une feuille de calcul si leur nom correspond à une référence de cellule valide. Si la fonction doit être utilisée comme fonction définie par l'utilisateur, elle doit être renommée. Sinon, sa visibilité devrait être réduite à 'Private', ou alors la fonction doit être déplacée vers un autre type de module.
+
Une annotation Rubberduck est spécifiée pour un module ou un membre, mais l'attribut correspondant a une valeur différente: les attributs devraient être synchronisés avec les annotations.
@@ -370,9 +379,6 @@ Si le paramètre peut être nul, ignorer ce résultat; passer une valeur nulle
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'.
-
- Une condition est toujours fausse, cause une erreur d'exécution, ou les effets cumulatifs de conditions précédentes représentent toutes les valeurs possibles, bref la condition a déjà été évaluée et ce bloc 'Case' est effectivement inatteignable.
-
VBA n'indiquera pas d'erreur au moment de la compilation si un objet est assigné à une variable avec un type incompatible au type déclaré. Dans la presque totalité des cas ceci causera une erreur à l'exécution. Pour tous les autres cas, un type compatible doit être utilisé.
@@ -427,9 +433,6 @@ Si le paramètre peut être nul, ignorer ce résultat; passer une valeur nulle
Un appel implicite d'un membre par défaut exécute du code de façon implicite (et parfois, sournoise). Même pour accéder à une collection à l'aide d'un index - rendre tous les appels explicites améliore généralement la lisibilité.
-
- Un membre est défini comme étant une fonction, mais son utilisation ne diffère en rien d'une procédure 'Sub' standard. Considérez convertir cette function en procédure.
-
La valeur renvoyée par une fonction est ignorée; la fonction est utilisée comme une procédure ('Sub'). Ceci peut être le résultat d'un simple oubli, ou alors la fonction est utilisée pour ses effets secondaires, l'existence desquels peut constituer un 'code smell'.
@@ -439,22 +442,28 @@ Si le paramètre peut être nul, ignorer ce résultat; passer une valeur nulle
Une annotation a plus d'arguments que permis; les arguments superflus seront ignorés.
-
- Une annotation est spécifiée dans un module d'un type qui n'est pas compatible avec cette annotation. Certaines annotations peuvent seulement être utilisées dans certains types de modules.
-
Les références implicites au classeur hôte dans un module de type 'Workbook' sont faciles à méprendre pour des références implicites au classeur actif (ActiveWorkbook). Qualifier l'appel avec 'Me' enlève cette ambiguité. Si l'intention est de référencer le classeur actif, qualifier avec 'ActiveWorkbook' pour prévenir un bogue.Les références implicites à la feuille hôte dans ce même module peuvent facilement être méprises pour des références à la feuille active (ActiveSheet). Qualifier l'appel avec 'Me' enlève l'ambiguité. Si l'intention est de référer à la feuille active, qualifier l'appel avec 'ActiveSheet' pour prévenir un bogue.
-
- L'annotation n'a pu être liée à une cible. Une annotation ciblant un module ne peut être utilisée pour une méthode; une annotation destinée à un membre ne peut être utilisée pour un module.
-
Le dernier paramètre ('Value' ou 'RHS') d'un membre Property Let ou Property Set est toujours passé par valeur (ByVal), et ce même en présence d'un modificateur ByRef, implicite ou explicite (sauf pour un type UDT).
+
+ Une annotation est spécifiée dans un module d'un type qui n'est pas compatible avec cette annotation. Certaines annotations peuvent seulement être utilisées dans certains types de modules.
+
Un commentaire correspond à la syntaxe pour une annotation valide, mais ne correspond à aucunne annotation supportée.
+
+ Tout tableau créé avec un appel à la fonction VBA.Array explicitement qualifié avec la librairie VBA aura toujours zéro pour base, en dépit de Option Base 1.
+
+
+ Tout tableau créé avec 'ParamArray' aura toujours zéro pour base, en dépit de Option Base 1.
+
+
+ La propriété en lecture seule 'Range.Cells' accepte deux paramètres optionnels, mais si aucun n'est spécifié alors une référence à l'objet 'Range' parent est retournée, ce qui rend l'appel entièrement superflu.
+
\ No newline at end of file
diff --git a/Rubberduck.Resources/Inspections/InspectionInfo.it.resx b/Rubberduck.Resources/Inspections/InspectionInfo.it.resx
index b7fa1b693c..97b99c545c 100644
--- a/Rubberduck.Resources/Inspections/InspectionInfo.it.resx
+++ b/Rubberduck.Resources/Inspections/InspectionInfo.it.resx
@@ -117,309 +117,288 @@
System.Resources.ResXResourceWriter, System.Windows.Forms, Version=4.0.0.0, Culture=neutral, PublicKeyToken=b77a5c561934e089
-
- L'oggetto Applicazione Excel non implementa direttamente l'interfaccia WorksheetFunction. Tutte le chiamate effettuate ai membri di WorksheetFunction vengono gestite come associazione tardiva e gli errori nel membro chiamato verranno restituiti racchiusi in un Variant di VbVarType.vbError. Ciò rende gli errori non intercettabili con i gestori di errori e aggiunge una riduzione delle prestazioni rispetto alle chiamate associate iniziali. Considera la possibilità di chiamare Application.WorksheetFunction in modo esplicito. Nota: se questa chiamata ha generato errori in passato, tali errori sono stati ignorati. Se si applica la soluzione rapida, è necessario disporre di una corretta gestione degli errori.
-
-
- Il compilatore VBA non genera un errore se un oggetto viene passato come argomento per un parametro con un tipo di oggetto dichiarato incompatibile, cioè con un tipo di oggetto che non è né lo stesso tipo, né un supertipo né un sottotipo. In quasi tutte le circostanze il passaggio di un argomento di questo tipo porta a un errore di runtime, che è più difficile da rilevare e indica un bug. In tutte le altre situazioni il codice può essere modificato per passare solo argomenti di tipi dichiarati compatibili.
-
Il parametro viene passato per valore, ma è assegnato un nuovo valore / riferimento. Considera invece di creare una copia locale se il chiamante non deve conoscere il nuovo valore. Se il chiamante dovesse vedere il nuovo valore, il parametro dovrebbe essere passato invece ByRef, e hai un bug.
-
- Un'assegnazione è immediatamente sovrascritta da un'altra assegnazione o non è mai referenziata.
-
-
- Un'annotazione Rubberduck è specificata per un modulo o un membro, ma l'attributo corrispondente ha un valore diverso. Gli attributi e le annotazioni del modulo devono essere sincronizzati.
-
-
- A un membro viene assegnato Vero / Falso in diversi rami di un'istruzione if senza altre istruzioni condizionali. Utilizza invece la condizione direttamente al membro.
-
Rubberduck non è riuscito a trovare alcun riferimento alla costante. Valuta la possibilità di rimuovere la dichiarazione inutilizzata.
-
- Il compilatore VBA non genera un errore se è richiesta una chiamata di membro predefinito indicizzato ma il tipo dichiarato dell'oggetto non dispone di un membro predefinito adatto. In quasi tutte le circostanze, questo porta a un errore di runtime 91 'Oggetto o variabile del blocco With non impostata' o 438 'L'oggetto non supporta questa proprietà o metodo' a seconda che l'oggetto abbia il valore 'Nothing' o meno, che è più difficile da rilevare e indica un bug.
-
Considera di nominare il tuo progetto VBA.
-
- L'utilizzo dell'istruzione 'Def[Type]' consente di specificare i tipi utilizzando un prefisso. Questo stile di denominazione è fortemente scoraggiato e dovrebbe essere evitato.
-
-
- Un'annotazione viene specificata più volte, mentre dovrebbe essere specificata solo una volta.
-
-
- Un blocco 'Case' vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
-
-
- Un ciclo 'Do ... While' vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
-
-
- Un ciclo 'Else' vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
+
+ La costante incorporata 'vbNullString' è un puntatore ad una stringa nulla che occupa 0 byte di memoria, che trasmette in modo inequivocabile l'intento di una stringa vuota.
-
- Un ciclo 'For Each ... Next' vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
+
+ Considera invece di esporre una proprietà.
-
- Un ciclo 'For ... Next' vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
+
+ I riferimenti impliciti al foglio attivo rendono il codice fragile ed è più difficile eseguire il debug. Considera l'idea di rendere espliciti questi riferimenti quando sono voluti e prediligi l'uso di riferimenti agli oggetti. Ignora se la chiamata del membro si riferisce a un tipo che Rubberduck non può risolvere.
-
- Un ramo condizionale vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
+
+ I riferimenti impliciti alla cartella di lavoro attiva rendono il codice fragile ed è più difficile eseguire il debug. Considera l'idea di rendere espliciti questi riferimenti quando sono voluti e prediligi l'uso di riferimenti agli oggetti. Ignora se la chiamata del membro si riferisce a un tipo che Rubberduck non può risolvere.
-
- I metodi senza istruzioni eseguibili sembra che stiano facendo qualcosa che in realtà non fanno, causando quindi un comportamento imprevisto.
+
+ I parametri sono passati per riferimento se non diversamente specificato, il che può creare confusione e causare bug. Preferire il passaggio di parametri per valore e specificare ByRef in modo esplicito quando si passano i parametri per riferimento.
-
- I moduli e le classi vuoti indicano funzionalità non ancora implementate o rappresentano un bagaglio non necessario che può danneggiare la manutenibilità di un progetto.
+
+ I membri del modulo sono pubblici per impostazione predefinita, mentre si può pensare il contrario. Considerare la possibilità di specificare modificatori di accesso esplicito per evitare ambiguità.
-
- La costante incorporata 'vbNullString' è un puntatore ad una stringa nulla che occupa 0 byte di memoria, che trasmette in modo inequivocabile l'intento di una stringa vuota.
+
+ I membri che restituiscono un valore implicitamente restituiscono un 'Variant' se non diversamente specificato. Prendi in considerazione la restituzione di un 'Variant' esplicito quando il tipo restituito non è noto o specificalo esplicitamente.
-
- Un blocco 'Loop' vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
+
+ Una variabile a livello di modulo utilizzata solo in una procedura dovrebbe essere dichiarata in quella procedura.
-
- Considera invece di esporre una proprietà.
+
+ Considerare la possibilità di continuare le firme lunghe tra i parametri. La suddivisione di una dichiarazione di parametro su più righe probabilmente danneggia la leggibilità.
-
- Una procedura che restituisce un oggetto può restituire 'Nothing'. Ciò causerà un errore di runtime 91 - 'Oggetto o variabile del blocco With non impostata' al successivo accesso al membro. Eseguire un controllo 'Is Nothing' dopo l'assegnazione 'Set' per evitare errori di runtime.
+
+ La dichiarazione di più variabili nella stessa istruzione è legale, ma dovrebbe essere usata con parsimonia. Considera la possibilità di dichiarare variabili più vicine al loro utilizzo, in una singola istruzione per dichiarazione.
-
- Le funzioni visibili in Excel come funzioni definite dall'utente restituiranno un errore '#REF!' quando sono utilizzate su un foglio di lavoro se corrispondono al nome di un riferimento di cella valido. Se la funzione deve essere utilizzata come UDF, deve essere rinominata. Se la funzione non è concepita per essere utilizzata come UDF, dovrebbe essere definita come 'Private' o spostata da un modulo standard.
+
+ Questo è probabilmente un bug. Il valore di ritorno di una funzione o del getter di una proprietà deve essere assegnato prima di uscire, altrimenti il programma non funzionerà con i risultati attesi. Se una funzione non ha un valore di ritorno significativo, considera invece di dichiararla come una procedura 'Sub'.
-
- Un membro è scritto come una funzione, ma è sempre utilizzato come una procedura. Valuta la possibilità di convertire la 'Function' in 'Sub'.
+
+ L'istruzione 'Call' non è più necessaria per chiamare le procedure ed esiste nel linguaggio solo per supportare il codice legacy che lo richiedeva; può essere riscritta in modo sicuro in una chiamata implicita.
-
- Il valore di ritorno di una funzione viene scartato, ovvero la funzione viene utilizzata come una procedura 'Sub'. O si tratta di una svista o la funzione viene utilizzata per altre finalità, la cui esistenza sarebbe anche un segnale d'allarme.
+
+ L'istruzione 'Rem' esiste nel linguaggio solo per supportare il codice legacy che lo richiedeva; può essere tranquillamente sostituito con un apostrofo / virgoletta singola di commento.
-
- Le espressioni tra parentesi vengono valutate dall'applicazione host in fase di esecuzione, il che significa che VBA non può convalidare l'espressione in fase di compilazione. Considerare invece l'utilizzo del modello a oggetti dell'applicazione host.
+
+ La parola chiave 'Global' esiste nel linguaggio solo per supportare il codice legacy che la richiedeva; può essere tranquillamente sostituita con il modificatore 'Public'.
-
- La notazione ungherese rende il codice meno leggibile ed è ridondante quando si utilizzano variabili fortemente tipizzate e nomi significativi.
+
+ L'istruzione 'Let' esiste nel linguaggio solo per supportare il codice legacy che lo richiedeva; può essere rimossa in modo sicuro, poiché il VBA moderno non richiede quella parola chiave per le assegnazioni di valore.
-
- Un modulo di classe che deve essere utilizzato come interfaccia per classi concrete dovrebbe generalmente essere astratto da qualsiasi implementazione. Se è tua intenzione utilizzare questo modulo di classe come un tipo concreto, puoi tranquillamente ignorare questo risultato dell'ispezione.
+
+ I caratteri di suggerimento del tipo esistono nel linguaggio solo per supportare il codice legacy che lo richiedeva; possono essere tranquillamente sostituiti nelle dichiarazioni con una clausola di tipo "As" che specifica esplicitamente il tipo e possono essere omessi in altri riferimenti a identificatori.
-
- I riferimenti impliciti al foglio attivo rendono il codice fragile ed è più difficile eseguire il debug. Considera l'idea di rendere espliciti questi riferimenti quando sono voluti e prediligi l'uso di riferimenti agli oggetti. Ignora se la chiamata del membro si riferisce a un tipo che Rubberduck non può risolvere.
+
+ Gli array sono in genere a base zero. Questa opzione modifica il limite inferiore predefinito per gli array di dimensioni implicite e può introdurre errori off-by-one se non si è cauti.
-
- I riferimenti impliciti alla cartella di lavoro attiva rendono il codice fragile ed è più difficile eseguire il debug. Considera l'idea di rendere espliciti questi riferimenti quando sono voluti e prediligi l'uso di riferimenti agli oggetti. Ignora se la chiamata del membro si riferisce a un tipo che Rubberduck non può risolvere.
+
+ VBA compilerà tranquillamente un errore di battitura: usa 'Option Explicit' per impedire la corretta compilazione di un programma errato.
-
- I parametri sono passati per riferimento se non diversamente specificato, il che può creare confusione e causare bug. Preferire il passaggio di parametri per valore e specificare ByRef in modo esplicito quando si passano i parametri per riferimento.
+
+ Un parametro che viene passato per riferimento e a cui non è assegnato un nuovo valore / riferimento, potrebbe invece essere passato per valore.
-
- I riferimenti impliciti ai membri della cartella di lavoro all'interno di un documento del modulo della cartella di lavoro possono essere errori per i riferimenti impliciti alla cartella di lavoro attiva, che è il comportamento in tutti gli altri moduli. Qualificando esplicitamente queste chiamate dei membri con Me, l'ambiguità può essere risolta.
+
+ Un parametro viene passato a un membro che non lo utilizza. Considera l'idea di rimuovere quel parametro.
-
- I riferimenti impliciti ai membri del foglio di lavoro all'interno di un documento del modulo del foglio di lavoro possono essere errori per i riferimenti impliciti al foglio di lavoro attivo, che è il comportamento in tutti gli altri moduli. Qualificando esplicitamente queste chiamate dei membri con Me, l'ambiguità può essere risolta.
+
+ Rubberduck non è riuscito a trovare alcun chiamante per una procedura. Se la procedura è agganciata a un macro-pulsante, usata come funzione definita dall'utente (UDF) o gestisce un evento dell'applicazione che Rubberduck non conosceva, puoi tranquillamente ignorare questo risultato dell'ispezione; in caso contrario, valutare la possibilità di rimuoverla.
-
- Gli accessi ai membri predefiniti nascondono il membro effettivamente chiamato. Ciò è particolarmente fuorviante se non vi è alcuna indicazione nell'espressione che tale chiamata sia stata effettuata. Può causare errori in cui un membro è stato dimenticato di essere chiamato passando inosservato.
+
+ Questo è probabilmente un bug. Si fa riferimento a una variabile, ma non viene mai assegnata.
-
- Se la clausola di tipo 'As' per una dichiarazione 'Const' non è inclusa, il tipo è implicito. Includere un 'As <Type>' esplicito sostituendo '<Type>' con il tipo di dati corretto per esplicitare il tipo del valore della costante.
+
+ Esiste una funzione equivalente che restituisce una stringa e dovrebbe essere utilizzata preferibilmente per evitare conversioni di tipo implicite.
+Se il parametro può essere nullo, ignorare questo risultato dell'ispezione; il passaggio di un valore nullo a una funzione che prevede una stringa genererebbe un errore di runtime di mancata corrispondenza del tipo.
-
- I membri del modulo sono pubblici per impostazione predefinita, mentre si può pensare il contrario. Considerare la possibilità di specificare modificatori di accesso esplicito per evitare ambiguità.
+
+ I nomi degli identificatori dovrebbero indicare per cosa sono usati e dovrebbero essere leggibili; evitare di togliere tutte le vocali, suffissi numerici e nomi di 1-2 caratteri.
-
- Gli accessi ai membri predefiniti nascondono il membro effettivamente chiamato. Ciò è particolarmente fuorviante se non vi è alcuna indicazione nell'espressione che tale chiamata viene effettuata e il membro predefinito finale non si trova sull'interfaccia dell'oggetto stesso. In particolare, questo può causare errori in cui un membro è stato dimenticato di essere chiamato passando inosservato.
+
+ La variabile non è assegnata. Se questo non è previsto, probabilmente c'è un bug. Ignorare questo risultato dell'ispezione se la variabile viene assegnata in un'altra procedura tramite un parametro ByRef.
-
- Gli accessi ai membri predefiniti nascondono il membro effettivamente chiamato. Ciò è particolarmente fuorviante se non vi è alcuna indicazione nell'espressione che tale chiamata viene effettuata e se il membro predefinito non può essere determinato dal tipo dichiarato dell'oggetto. Di conseguenza, con errori in cui un membro è stato dimenticato di essere chiamato passando inosservato e se non ci fosse un membro predefinito adatto in fase di esecuzione, verrà generato un errore 438 'L'oggetto non supporta questa proprietà o metodo'.
+
+ La variabile non ha riferimenti
-
- I membri che restituiscono un valore implicitamente restituiscono un 'Variant' se non diversamente specificato. Prendi in considerazione la restituzione di un 'Variant' esplicito quando il tipo restituito non è noto o specificalo esplicitamente.
+
+ Una variabile il cui tipo non è dichiarato esplicitamente è implicitamente 'Variant'. Considera l'idea di renderla una 'Variant' esplicita, se previsto, o di dichiarare un tipo più specifico.
-
- Un accesso al membro predefinito nasconde quale membro è effettivamente chiamato. Sebbene sia evidente che ci sia una chiamata nel caso di accesso indicizzato ad un membro predefinito, esplicitarlo di solito è meglio per la leggibilità.
+
+ Una proprietà che espone un mutatore ma nessuna funzione di accesso è indice di errore nella struttura e crea un'API confusa. Considera l'idea di esporre un getter o di convertire il mutatore in un metodo.
-
- Un accesso al membro predefinito nasconde quale membro è effettivamente chiamato. Sebbene sia evidente che ci sia una chiamata nel caso di accesso indicizzato ad un membro predefinito, eplicitarlo di solito è meglio per la leggibilità. Ciò vale soprattutto se il membro predefinito a cui si accede non si trova sull'interfaccia dell'oggetto stesso ma deve essere risolto tramite una catena di chiamate ai membri predefiniti.
+
+ Una procedura che ha un solo parametro passato per riferimento a cui viene assegnato un nuovo valore / riferimento prima che la procedura termini, utilizza un parametro ByRef come valore di ritorno: considera invece di renderla una funzione.
-
- Un accesso al membro predefinito nasconde quale membro è effettivamente chiamato. Sebbene sia evidente che ci sia una chiamata nel caso di accesso indicizzato ad un membro predefinito, eplicitarlo di solito è meglio per la leggibilità. A maggior ragione se il membro predefinito non può essere determinato in fase di compilazione. Inoltre, se non c'è un membro predefinito adatto in fase di esecuzione, sarà generato un errore 438 'L'oggetto non supporta questa proprietà o metodo'.
+
+ Una dichiarazione di variabile oggetto istanziata automaticamente nell'ambito della procedura cambia il funzionamento dell'annullamento del riferimento, il che può portare a un comportamento imprevisto.
-
- Il valore massimo di un intero con segno a 16 bit è 32.767 - l'utilizzo di un tipo di dati intero a 32 bit (Long) ove possibile può aiutare a prevenire errori di runtime di 'Overflow' ed è gestito meglio dalle moderne CPU.
+
+ Un membro è scritto come una funzione, ma è sempre utilizzato come una procedura. Valuta la possibilità di convertire la 'Function' in 'Sub'.
-
- IsMissing deve essere chiamato solo su argomenti opzionali e restituirà risultati corretti solo se il tipo di argomento è 'Variant' senza un valore predefinito esplicito. Tutti gli altri usi restituiranno 'False'.
+
+ Per quanto ne sa Rubberduck, questa variabile è una variabile oggetto, assegnata senza la parola chiave 'Set'. Ciò causa l'errore 91 di runtime 'Oggetto o variabile del blocco With non impostata' o 438 'L'oggetto non supporta questa proprietà o metodo' a seconda che la variabile abbia o meno il valore 'Nothing'.
-
- IsMissing deve essere chiamato solo su argomenti della procedura che lo contiene e quasi tutti gli altri utilizzi restituiranno 'False'. Il passaggio di qualsiasi altra espressione alla funzione equivale a 'VarType({expression}) = vbError' e in rari casi può causare l'arresto anomalo dell'applicazione host.
+
+ Un parametro di annotazione è mancante o specificato in modo errato. La sintassi corretta è: '@Annotation([parameter])\nExample: '@Folder("Parent.Child")
-
- Una parola chiave è utilizzata come membro in un'enumerazione o in un tipo definito dall'utente. Ciò può portare a una risoluzione ambigua. Valuta la possibilità di rinominare il membro.
+
+ La parola chiave 'Public' può essere utilizzata solo a livello di modulo; anche la sua controparte 'Private' può essere utilizzata solo a livello di modulo. Tuttavia, 'Dim' può essere utilizzato per dichiarare le variabili a livello sia della procedura sia del modulo. Per coerenza, sarebbe preferibile riservare 'Dim' per le variabili locali e quindi utilizzare 'Private' invece di 'Dim' a livello di modulo.
-
- Sono presenti continuazioni di riga tra le parole chiave. Non c'è una buona ragione per metterle lì; considera la possibilità di rimuoverle del tutto.
+
+ Il codice che utilizza variabili non dichiarate non viene compilato quando viene specificato Option Explicit. Le variabili non dichiarate sono sempre Variant, un tipo di dati che incorre in overhead e archiviazione non necessari.
-
- Un'etichetta di riga a cui non si salta mai ('GoTo', 'Resume', ...) non serve a nulla. Considera l'idea di rimuoverla.
+
+ La notazione ungherese rende il codice meno leggibile ed è ridondante quando si utilizzano variabili fortemente tipizzate e nomi significativi.Viene effettuata una chiamata di accesso ad un membro su un'interfaccia estesa che Rubberduck non è riuscito a risolvere, o il membro non è stato trovato. Se VBA non è in grado di risolvere il tipo in fase di esecuzione, sarà generato l'errore 438. Se è disponibile un'interfaccia equivalente e non estesa che Rubberduck può risolvere, prendi in considerazione di usarla.
-
- L'ultimo parametro (il parametro 'Value') dei mutatori di proprietà è sempre passato da ByVal. Questo vale indipendentemente dalla presenza o assenza di un modificatore ByRef o ByVal. Eccezione: un UserDefinedType deve sempre essere passato ByRef anche quando è l'ultimo parametro di un mutatore di proprietà.
+
+ Le espressioni tra parentesi vengono valutate dall'applicazione host in fase di esecuzione, il che significa che VBA non può convalidare l'espressione in fase di compilazione. Considerare invece l'utilizzo del modello a oggetti dell'applicazione host.
-
- Un parametro di annotazione è mancante o specificato in modo errato. La sintassi corretta è: '@Annotation([parameter])\nExample: '@Folder("Parent.Child")
+
+ L'oggetto Applicazione Excel non implementa direttamente l'interfaccia WorksheetFunction. Tutte le chiamate effettuate ai membri di WorksheetFunction vengono gestite come associazione tardiva e gli errori nel membro chiamato verranno restituiti racchiusi in un Variant di VbVarType.vbError. Ciò rende gli errori non intercettabili con i gestori di errori e aggiunge una riduzione delle prestazioni rispetto alle chiamate associate iniziali. Considera la possibilità di chiamare Application.WorksheetFunction in modo esplicito. Nota: se questa chiamata ha generato errori in passato, tali errori sono stati ignorati. Se si applica la soluzione rapida, è necessario disporre di una corretta gestione degli errori.
-
- Un'annotazione di Rubberduck è specificata per un modulo o un membro, ma l'attributo corrispondente non è presente. Gli attributi e le annotazioni del modulo devono essere sincronizzati.
+
+ Questa è l'impostazione predefinita, non è necessario specificarla.
-
- Gli attributi dei membri non vengono visualizzati in VBE. Aggiungendo un'annotazione, rendi questi attributi più espliciti e Rubberduck può mantenere sincronizzati annotazioni e attributi.
+
+ Non è stato possibile associare l'annotazione a una destinazione. L'annotazione è fuori posto? Un'annotazione destinata a essere specificata a livello di modulo non può essere utilizzata per annotare i membri; al contrario, le annotazioni intese come annotazioni di membri non possono essere utilizzate a livello di modulo.
-
- Gli attributi del modulo non vengono visualizzati nel VBE. Aggiungendo un'annotazione, rendi questi attributi più espliciti e Rubberduck può mantenere sincronizzati annotazioni e attributi.
+
+ Un'annotazione di Rubberduck è specificata per un modulo o un membro, ma l'attributo corrispondente non è presente. Gli attributi e le annotazioni del modulo devono essere sincronizzati.
-
- La parola chiave 'Public' può essere utilizzata solo a livello di modulo; anche la sua controparte 'Private' può essere utilizzata solo a livello di modulo. Tuttavia, 'Dim' può essere utilizzato per dichiarare le variabili a livello sia della procedura sia del modulo. Per coerenza, sarebbe preferibile riservare 'Dim' per le variabili locali e quindi utilizzare 'Private' invece di 'Dim' a livello di modulo.
+
+ Un ramo condizionale vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
-
- I moduli senza l'annotazione '@Folder' non possono ricevere raggruppamenti personalizzati in Explorer del Codice.
+
+ Essendo l'impostazione predefinita/implicita per questa opzione, questa istruzione può essere tranquillamente omessa.
-
- Una variabile a livello di modulo utilizzata solo in una procedura dovrebbe essere dichiarata in quella procedura.
+
+ Per impostazione predefinita, tutti i parametri vengono passati per riferimento, quindi non è necessario includere il modificatore 'ByRef'.
-
- Considerare la possibilità di continuare le firme lunghe tra i parametri. La suddivisione di una dichiarazione di parametro su più righe probabilmente danneggia la leggibilità.
+
+ Un'etichetta di riga a cui non si salta mai ('GoTo', 'Resume', ...) non serve a nulla. Considera l'idea di rimuoverla.
-
- La dichiarazione di più variabili nella stessa istruzione è legale, ma dovrebbe essere usata con parsimonia. Considera la possibilità di dichiarare variabili più vicine al loro utilizzo, in una singola istruzione per dichiarazione.
+
+ Un ciclo 'Else' vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
-
- I numeri di riga negativi vengono effettivamente inseriti come letterali esadecimali e quindi ottimizzati da VBE. Modificare di nuovo la riga la farà diventare rossa poiché i numeri di riga negativi sono di fatto illegali.
+
+ Il valore massimo di un intero con segno a 16 bit è 32.767 - l'utilizzo di un tipo di dati intero a 32 bit (Long) ove possibile può aiutare a prevenire errori di runtime di 'Overflow' ed è gestito meglio dalle moderne CPU.
-
- L'identificatore contiene uno spazio non separatore che assomiglia molto a uno spazio normale (illegale nel nome di un identificatore), che offusca il codice e crea un'esperienza confusa. Considera l'idea di utilizzare caratteri visibili per gli identificatori.
+
+ La parola chiave 'Stop' interrompe l'esecuzione e fa apparire il debugger. Evita il suo utilizzo nel codice distribuito.
-
- Questo è probabilmente un bug. Il valore di ritorno di una funzione o del getter di una proprietà deve essere assegnato prima di uscire, altrimenti il programma non funzionerà con i risultati attesi. Se una funzione non ha un valore di ritorno significativo, considera invece di dichiararla come una procedura 'Sub'.
+
+ Un blocco 'Case' vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
-
- Per quanto ne sa Rubberduck, questa variabile è una variabile oggetto, assegnata senza la parola chiave 'Set'. Ciò causa l'errore 91 di runtime 'Oggetto o variabile del blocco With non impostata' o 438 'L'oggetto non supporta questa proprietà o metodo' a seconda che la variabile abbia o meno il valore 'Nothing'.
+
+ Un ciclo 'Do ... While' vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
-
- L'utilizzo di un oggetto con un membro predefinito in una posizione che richiede una procedura porta a una chiamata implicita del membro predefinito. Questo è molto probabilmente non intenzionale e influisce negativamente sulla leggibilità.
+
+ Un ciclo 'For Each ... Next' vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
-
- Le implementazioni di Windows di Visual Basic supportano solo la convenzione di chiamata StdCall. La convenzione di chiamata CDecl è supportata solo nelle versioni Macintosh di VBA. L'uso di questa parola chiave in Windows provocherà l'errore di runtime 49 - 'Convenzione di chiamata DLL non valida'. Se questa procedura deve essere utilizzata solo su host Macintosh, dovrebbe essere compilata in modo condizionale.
+
+ Un ciclo 'For ... Next' vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
-
- L'istruzione 'Call' non è più necessaria per chiamare le procedure ed esiste nel linguaggio solo per supportare il codice legacy che lo richiedeva; può essere riscritta in modo sicuro in una chiamata implicita.
+
+ Un blocco 'Loop' vuoto senza alcuna istruzione eseguibile, lascia un manutentore a chiedersi quale sia l'intento del codice. Evita di scrivere codice che non serve.
-
- L'istruzione 'Rem' esiste nel linguaggio solo per supportare il codice legacy che lo richiedeva; può essere tranquillamente sostituito con un apostrofo / virgoletta singola di commento.
+
+ Due dichiarazioni nell'ambito di validità hanno lo stesso nome identificativo. Prendi in considerazione l'utilizzo di nomi di identificatori completi, altrimenti solo uno di essi sarà disponibile per l'uso.L'istruzione 'Error' esiste nel linguaggio solo per supportare il codice legacy che lo richiedeva; è meglio invece usare 'Err.Raise'.
-
- La parola chiave 'Global' esiste nel linguaggio solo per supportare il codice legacy che la richiedeva; può essere tranquillamente sostituita con il modificatore 'Public'.
+
+ A un membro viene assegnato Vero / Falso in diversi rami di un'istruzione if senza altre istruzioni condizionali. Utilizza invece la condizione direttamente al membro.
-
- L'istruzione 'Let' esiste nel linguaggio solo per supportare il codice legacy che lo richiedeva; può essere rimossa in modo sicuro, poiché il VBA moderno non richiede quella parola chiave per le assegnazioni di valore.
+
+ I moduli e le classi vuoti indicano funzionalità non ancora implementate o rappresentano un bagaglio non necessario che può danneggiare la manutenibilità di un progetto.
+
+
+ Una condizione 'Case' o restituisce sempre False, causando un errore in fase di esecuzione, o l'effetto cumulativo delle precedenti istruzioni 'Case' rappresenta tutti i valori possibili o un sovrainsieme dei valori dell'istruzione 'Case'. Di conseguenza, il blocco 'Case' non sarà mai eseguito ed è "codice inattivo" oppure l'istruzione 'Case' è un errore in fase di esecuzione in attesa di verificarsi. Valuta la possibilità di rimuovere, riordinare o modificare l'istruzione 'Case'.
+
+
+ La gestione degli errori dovrebbe essere ripristinata dopo aver utilizzato 'On Error Resume Next'.
+
+
+ L'utilizzo dell'istruzione 'Def[Type]' consente di specificare i tipi utilizzando un prefisso. Questo stile di denominazione è fortemente scoraggiato e dovrebbe essere evitato.
+
+
+ Il passo del ciclo for-next non è specificato. Questo potrebbe non essere intenzionale.
+
+
+ 1 è il passo predefinito in un ciclo for-next e quindi è ridondante.
+
+
+ Excel definisce già una variabile oggetto con ambito globale con questo riferimento. Prendi in considerazione l'utilizzo della proprietà 'CodeName' del foglio.Questo membro è contrassegnato come '@Obsolete'. Non dovrebbe più essere utilizzato, dovrebbe esserci un'alternativa migliore.
-
- I caratteri di suggerimento del tipo esistono nel linguaggio solo per supportare il codice legacy che lo richiedeva; possono essere tranquillamente sostituiti nelle dichiarazioni con una clausola di tipo "As" che specifica esplicitamente il tipo e possono essere omessi in altri riferimenti a identificatori.
+
+ Le implementazioni di Windows di Visual Basic supportano solo la convenzione di chiamata StdCall. La convenzione di chiamata CDecl è supportata solo nelle versioni Macintosh di VBA. L'uso di questa parola chiave in Windows provocherà l'errore di runtime 49 - 'Convenzione di chiamata DLL non valida'. Se questa procedura deve essere utilizzata solo su host Macintosh, dovrebbe essere compilata in modo condizionale.
-
- I cicli 'While ... Wend' esistono per compatibilità con le versioni precedenti e sono stati sostituiti dall'introduzione dei blocchi 'Do While ... Loop', che supportano l'istruzione di uscita 'Exit Do'. Non è possibile uscire dai cicli 'While ... Wend' se non soddisfacendo la condizione 'While'.
+
+ Un'annotazione viene specificata più volte, mentre dovrebbe essere specificata solo una volta.
-
- Sebbene ciò sia legale, questa è una "caratteristica" scarsamente documentata che significa qualcosa di diverso -- anche lo stato di errore viene cancellato oltre a disabilitare qualsiasi gestione degli errori. Tuttavia, questo può essere ambiguo in quanto un'etichetta di riga negativa di -1 può finire come obiettivo e una gestione degli errori eccessivamente complessa di solito indica la necessità di refactoring della procedura.
+
+ I moduli senza l'annotazione '@Folder' non possono ricevere raggruppamenti personalizzati in Explorer del Codice.On Local Error esiste solo per compatibilità con le versioni precedenti di Visual Basic e tutti gli errori vengono considerati come locali indipendentemente dall'istruzione On Local Error. L'uso improprio di questa parola chiave dà l'impressione che esista una distinzione tra i tipi di gestione degli errori mentre in realtà non esiste.
-
- Gli array sono in genere a base zero. Questa opzione modifica il limite inferiore predefinito per gli array di dimensioni implicite e può introdurre errori off-by-one se non si è cauti.
-
-
- Questa è l'impostazione predefinita, non è necessario specificarla.
-
-
- VBA compilerà tranquillamente un errore di battitura: usa 'Option Explicit' per impedire la corretta compilazione di un programma errato.
-
-
- Un parametro che viene passato per riferimento e a cui non è assegnato un nuovo valore / riferimento, potrebbe invece essere passato per valore.
+
+ IsMissing deve essere chiamato solo su argomenti opzionali e restituirà risultati corretti solo se il tipo di argomento è 'Variant' senza un valore predefinito esplicito. Tutti gli altri usi restituiranno 'False'.
-
- Un parametro viene passato a un membro che non lo utilizza. Considera l'idea di rimuovere quel parametro.
+
+ IsMissing deve essere chiamato solo su argomenti della procedura che lo contiene e quasi tutti gli altri utilizzi restituiranno 'False'. Il passaggio di qualsiasi altra espressione alla funzione equivale a 'VarType({expression}) = vbError' e in rari casi può causare l'arresto anomalo dell'applicazione host.
-
- Una procedura che ha un solo parametro passato per riferimento a cui viene assegnato un nuovo valore / riferimento prima che la procedura termini, utilizza un parametro ByRef come valore di ritorno: considera invece di renderla una funzione.
+
+ Un'assegnazione è immediatamente sovrascritta da un'altra assegnazione o non è mai referenziata.
-
- Rubberduck non è riuscito a trovare alcun chiamante per una procedura. Se la procedura è agganciata a un macro-pulsante, usata come funzione definita dall'utente (UDF) o gestisce un evento dell'applicazione che Rubberduck non conosceva, puoi tranquillamente ignorare questo risultato dell'ispezione; in caso contrario, valutare la possibilità di rimuoverla.
+
+ Un modulo di classe che contiene membri con il trattino basso non può essere implementato da altre classi. Il carattere trattino basso viene utilizzato come separatore tra il nome dell'interfaccia / oggetto e il nome del membro implementato: avere un carattere trattino basso nel nome del membro confonde il compilatore, che quindi si rifiuta di compilare il progetto. Evita i caratteri trattino basso nei nomi dei membri pubblici seguendo una convenzione di denominazione 'PascalCase'.
-
- Il compilatore VBA non genera un errore se una variabile oggetto viene utilizzata in un punto che richiede una procedura e il tipo dichiarato dell'oggetto non dispone di un membro predefinito appropriato. In quasi tutte le circostanze, questo porta a un errore di runtime 91 'Oggetto o variabile del blocco With non impostata' o 438 'L'oggetto non supporta questa proprietà o metodo' a seconda che l'oggetto abbia il valore 'Nothing' o meno, che è più difficile da rilevare e indica un bug.
+
+ Una procedura che restituisce un oggetto può restituire 'Nothing'. Ciò causerà un errore di runtime 91 - 'Oggetto o variabile del blocco With non impostata' al successivo accesso al membro. Eseguire un controllo 'Is Nothing' dopo l'assegnazione 'Set' per evitare errori di runtime.
-
- Per impostazione predefinita, tutti i parametri vengono passati per riferimento, quindi non è necessario includere il modificatore 'ByRef'.
+
+ Le funzioni visibili in Excel come funzioni definite dall'utente restituiranno un errore '#REF!' quando sono utilizzate su un foglio di lavoro se corrispondono al nome di un riferimento di cella valido. Se la funzione deve essere utilizzata come UDF, deve essere rinominata. Se la funzione non è concepita per essere utilizzata come UDF, dovrebbe essere definita come 'Private' o spostata da un modulo standard.
-
- Essendo l'impostazione predefinita/implicita per questa opzione, questa istruzione può essere tranquillamente omessa.
+
+ Un'annotazione Rubberduck è specificata per un modulo o un membro, ma l'attributo corrispondente ha un valore diverso. Gli attributi e le annotazioni del modulo devono essere sincronizzati.
-
- Una dichiarazione di variabile oggetto istanziata automaticamente nell'ambito della procedura cambia il funzionamento dell'annullamento del riferimento, il che può portare a un comportamento imprevisto.
+
+ Gli attributi dei membri non vengono visualizzati in VBE. Aggiungendo un'annotazione, rendi questi attributi più espliciti e Rubberduck può mantenere sincronizzati annotazioni e attributi.
-
- Il compilatore VBA non genera un errore se un oggetto è assegnato a una variabile con un tipo di oggetto dichiarato incompatibile, cioè con un tipo di oggetto che non è né lo stesso tipo, né un supertipo né un sottotipo. In quasi tutte le circostanze una tale assegnazione porta a un errore di runtime, che è più difficile da rilevare e indica un bug. In tutte le altre situazioni il codice può essere modificato per utilizzare solo assegnazioni tra tipi dichiarati compatibili.
+
+ Gli attributi del modulo non vengono visualizzati nel VBE. Aggiungendo un'annotazione, rendi questi attributi più espliciti e Rubberduck può mantenere sincronizzati annotazioni e attributi.
-
- Due dichiarazioni nell'ambito di validità hanno lo stesso nome identificativo. Prendi in considerazione l'utilizzo di nomi di identificatori completi, altrimenti solo uno di essi sarà disponibile per l'uso.
+
+ Una parola chiave è utilizzata come membro in un'enumerazione o in un tipo definito dall'utente. Ciò può portare a una risoluzione ambigua. Valuta la possibilità di rinominare il membro.
-
- Excel definisce già una variabile oggetto con ambito globale con questo riferimento. Prendi in considerazione l'utilizzo della proprietà 'CodeName' del foglio.
+
+ Sono presenti continuazioni di riga tra le parole chiave. Non c'è una buona ragione per metterle lì; considera la possibilità di rimuoverle del tutto.
-
- Il passo del ciclo for-next non è specificato. Questo potrebbe non essere intenzionale.
+
+ L'identificatore contiene uno spazio non separatore che assomiglia molto a uno spazio normale (illegale nel nome di un identificatore), che offusca il codice e crea un'esperienza confusa. Considera l'idea di utilizzare caratteri visibili per gli identificatori.
-
- 1 è il passo predefinito in un ciclo for-next e quindi è ridondante.
+
+ I numeri di riga negativi vengono effettivamente inseriti come letterali esadecimali e quindi ottimizzati da VBE. Modificare di nuovo la riga la farà diventare rossa poiché i numeri di riga negativi sono di fatto illegali.
-
- La parola chiave 'Stop' interrompe l'esecuzione e fa apparire il debugger. Evita il suo utilizzo nel codice distribuito.
+
+ Sebbene ciò sia legale, questa è una "caratteristica" scarsamente documentata che significa qualcosa di diverso -- anche lo stato di errore viene cancellato oltre a disabilitare qualsiasi gestione degli errori. Tuttavia, questo può essere ambiguo in quanto un'etichetta di riga negativa di -1 può finire come obiettivo e una gestione degli errori eccessivamente complessa di solito indica la necessità di refactoring della procedura.
-
- Un'annotazione ha più argomenti di quelli consentiti; gli argomenti superflui sono ignorati.
+
+ I cicli 'While ... Wend' esistono per compatibilità con le versioni precedenti e sono stati sostituiti dall'introduzione dei blocchi 'Do While ... Loop', che supportano l'istruzione di uscita 'Exit Do'. Non è possibile uscire dai cicli 'While ... Wend' se non soddisfacendo la condizione 'While'.
-
- Ogni volta che entrambi i termini di un'assegnazione senza Set sono oggetti, c'è un'assegnazione dal membro predefinito dell'RHS a quello dell'LHS. Sebbene ciò possa essere intenzionale, in molte situazioni maschererà semplicemente un Set dimenticato per errore.
+
+ Il compilatore VBA non genera un errore se un oggetto è assegnato a una variabile con un tipo di oggetto dichiarato incompatibile, cioè con un tipo di oggetto che non è né lo stesso tipo, né un supertipo né un sottotipo. In quasi tutte le circostanze una tale assegnazione porta a un errore di runtime, che è più difficile da rilevare e indica un bug. In tutte le altre situazioni il codice può essere modificato per utilizzare solo assegnazioni tra tipi dichiarati compatibili.
-
- Questo è probabilmente un bug. Si fa riferimento a una variabile, ma non viene mai assegnata.
+
+ I metodi senza istruzioni eseguibili sembra che stiano facendo qualcosa che in realtà non fanno, causando quindi un comportamento imprevisto.
-
- Il codice che utilizza variabili non dichiarate non viene compilato quando viene specificato Option Explicit. Le variabili non dichiarate sono sempre Variant, un tipo di dati che incorre in overhead e archiviazione non necessari.
+
+ Un modulo di classe che deve essere utilizzato come interfaccia per classi concrete dovrebbe generalmente essere astratto da qualsiasi implementazione. Se è tua intenzione utilizzare questo modulo di classe come un tipo concreto, puoi tranquillamente ignorare questo risultato dell'ispezione.
-
- Un modulo di classe che contiene membri con il trattino basso non può essere implementato da altre classi. Il carattere trattino basso viene utilizzato come separatore tra il nome dell'interfaccia / oggetto e il nome del membro implementato: avere un carattere trattino basso nel nome del membro confonde il compilatore, che quindi si rifiuta di compilare il progetto. Evita i caratteri trattino basso nei nomi dei membri pubblici seguendo una convenzione di denominazione 'PascalCase'.
+
+ Il compilatore VBA non genera un errore se un oggetto viene passato come argomento per un parametro con un tipo di oggetto dichiarato incompatibile, cioè con un tipo di oggetto che non è né lo stesso tipo, né un supertipo né un sottotipo. In quasi tutte le circostanze il passaggio di un argomento di questo tipo porta a un errore di runtime, che è più difficile da rilevare e indica un bug. In tutte le altre situazioni il codice può essere modificato per passare solo argomenti di tipi dichiarati compatibili.
-
- La gestione degli errori dovrebbe essere ripristinata dopo aver utilizzato 'On Error Resume Next'.
+
+ Il compilatore VBA non genera un errore se un oggetto viene utilizzato in una posizione che richiede un tipo di valore e il tipo dichiarato dell'oggetto non dispone di un membro predefinito appropriato. In quasi tutte le circostanze, questo porta a un errore di runtime 91 'Oggetto o variabile del blocco With non impostata' o 438 'L'oggetto non supporta questa proprietà o metodo' a seconda che l'oggetto abbia il valore 'Nothing' o meno, che è più difficile da rilevare e indica un bug.
-
- Una condizione 'Case' o restituisce sempre False, causando un errore in fase di esecuzione, o l'effetto cumulativo delle precedenti istruzioni 'Case' rappresenta tutti i valori possibili o un sovrainsieme dei valori dell'istruzione 'Case'. Di conseguenza, il blocco 'Case' non sarà mai eseguito ed è "codice inattivo" oppure l'istruzione 'Case' è un errore in fase di esecuzione in attesa di verificarsi. Valuta la possibilità di rimuovere, riordinare o modificare l'istruzione 'Case'.
+
+ Il compilatore VBA non genera un errore se una variabile oggetto viene utilizzata in un punto che richiede una procedura e il tipo dichiarato dell'oggetto non dispone di un membro predefinito appropriato. In quasi tutte le circostanze, questo porta a un errore di runtime 91 'Oggetto o variabile del blocco With non impostata' o 438 'L'oggetto non supporta questa proprietà o metodo' a seconda che l'oggetto abbia il valore 'Nothing' o meno, che è più difficile da rilevare e indica un bug.
-
- Esiste una funzione equivalente che restituisce una stringa e dovrebbe essere utilizzata preferibilmente per evitare conversioni di tipo implicite.
-Se il parametro può essere nullo, ignorare questo risultato dell'ispezione; il passaggio di un valore nullo a una funzione che prevede una stringa genererebbe un errore di runtime di mancata corrispondenza del tipo.
+
+ Il compilatore VBA non genera un errore se è richiesta una chiamata di membro predefinito indicizzato ma il tipo dichiarato dell'oggetto non dispone di un membro predefinito adatto. In quasi tutte le circostanze, questo porta a un errore di runtime 91 'Oggetto o variabile del blocco With non impostata' o 438 'L'oggetto non supporta questa proprietà o metodo' a seconda che l'oggetto abbia il valore 'Nothing' o meno, che è più difficile da rilevare e indica un bug.La notazione con il punto escalmativo, formalmente nota come espressione di accesso al dizionario, solo apparentemente è fortemente tipizzata. Si tratta in realtà di un accesso di tipo stringa al membro parametrizzato come predefinito dell'oggetto su cui viene utilizzata.
@@ -430,26 +409,47 @@ Se il parametro può essere nullo, ignorare questo risultato dell'ispezione; il
La notazione con il punto escalmativo, formalmente nota come espressione di accesso al dizionario, solo apparentemente è fortemente tipizzata. Si tratta in realtà di un accesso di tipo stringa al membro parametrizzato come predefinito dell'oggetto su cui viene utilizzata. Ciò è particolarmente fuorviante: il membro predefinito non può essere determinato in fase di compilazione.
-
- Il compilatore VBA non genera un errore se un oggetto viene utilizzato in una posizione che richiede un tipo di valore e il tipo dichiarato dell'oggetto non dispone di un membro predefinito appropriato. In quasi tutte le circostanze, questo porta a un errore di runtime 91 'Oggetto o variabile del blocco With non impostata' o 438 'L'oggetto non supporta questa proprietà o metodo' a seconda che l'oggetto abbia il valore 'Nothing' o meno, che è più difficile da rilevare e indica un bug.
+
+ L'utilizzo di un oggetto con un membro predefinito in una posizione che richiede una procedura porta a una chiamata implicita del membro predefinito. Questo è molto probabilmente non intenzionale e influisce negativamente sulla leggibilità.
-
- La variabile non è assegnata. Se questo non è previsto, probabilmente c'è un bug. Ignorare questo risultato dell'ispezione se la variabile viene assegnata in un'altra procedura tramite un parametro ByRef.
+
+ Un accesso al membro predefinito nasconde quale membro è effettivamente chiamato. Sebbene sia evidente che ci sia una chiamata nel caso di accesso indicizzato ad un membro predefinito, esplicitarlo di solito è meglio per la leggibilità.
-
- La variabile non ha riferimenti
+
+ Un accesso al membro predefinito nasconde quale membro è effettivamente chiamato. Sebbene sia evidente che ci sia una chiamata nel caso di accesso indicizzato ad un membro predefinito, eplicitarlo di solito è meglio per la leggibilità. Ciò vale soprattutto se il membro predefinito a cui si accede non si trova sull'interfaccia dell'oggetto stesso ma deve essere risolto tramite una catena di chiamate ai membri predefiniti.
-
- Una variabile il cui tipo non è dichiarato esplicitamente è implicitamente 'Variant'. Considera l'idea di renderla una 'Variant' esplicita, se previsto, o di dichiarare un tipo più specifico.
+
+ Un accesso al membro predefinito nasconde quale membro è effettivamente chiamato. Sebbene sia evidente che ci sia una chiamata nel caso di accesso indicizzato ad un membro predefinito, eplicitarlo di solito è meglio per la leggibilità. A maggior ragione se il membro predefinito non può essere determinato in fase di compilazione. Inoltre, se non c'è un membro predefinito adatto in fase di esecuzione, sarà generato un errore 438 'L'oggetto non supporta questa proprietà o metodo'.
-
- Una proprietà che espone un mutatore ma nessuna funzione di accesso è indice di errore nella struttura e crea un'API confusa. Considera l'idea di esporre un getter o di convertire il mutatore in un metodo.
+
+ Gli accessi ai membri predefiniti nascondono il membro effettivamente chiamato. Ciò è particolarmente fuorviante se non vi è alcuna indicazione nell'espressione che tale chiamata sia stata effettuata. Può causare errori in cui un membro è stato dimenticato di essere chiamato passando inosservato.
-
- I nomi degli identificatori dovrebbero indicare per cosa sono usati e dovrebbero essere leggibili; evitare di togliere tutte le vocali, suffissi numerici e nomi di 1-2 caratteri.
+
+ Gli accessi ai membri predefiniti nascondono il membro effettivamente chiamato. Ciò è particolarmente fuorviante se non vi è alcuna indicazione nell'espressione che tale chiamata viene effettuata e il membro predefinito finale non si trova sull'interfaccia dell'oggetto stesso. In particolare, questo può causare errori in cui un membro è stato dimenticato di essere chiamato passando inosservato.
-
- Non è stato possibile associare l'annotazione a una destinazione. L'annotazione è fuori posto? Un'annotazione destinata a essere specificata a livello di modulo non può essere utilizzata per annotare i membri; al contrario, le annotazioni intese come annotazioni di membri non possono essere utilizzate a livello di modulo.
+
+ Gli accessi ai membri predefiniti nascondono il membro effettivamente chiamato. Ciò è particolarmente fuorviante se non vi è alcuna indicazione nell'espressione che tale chiamata viene effettuata e se il membro predefinito non può essere determinato dal tipo dichiarato dell'oggetto. Di conseguenza, con errori in cui un membro è stato dimenticato di essere chiamato passando inosservato e se non ci fosse un membro predefinito adatto in fase di esecuzione, verrà generato un errore 438 'L'oggetto non supporta questa proprietà o metodo'.
+
+
+ Ogni volta che entrambi i termini di un'assegnazione senza Set sono oggetti, c'è un'assegnazione dal membro predefinito dell'RHS a quello dell'LHS. Sebbene ciò possa essere intenzionale, in molte situazioni maschererà semplicemente un Set dimenticato per errore.
+
+
+ Il valore di ritorno di una funzione viene scartato, ovvero la funzione viene utilizzata come una procedura 'Sub'. O si tratta di una svista o la funzione viene utilizzata per altre finalità, la cui esistenza sarebbe anche un segnale d'allarme.
+
+
+ Se la clausola di tipo 'As' per una dichiarazione 'Const' non è inclusa, il tipo è implicito. Includere un 'As <Type>' esplicito sostituendo '<Type>' con il tipo di dati corretto per esplicitare il tipo del valore della costante.
+
+
+ Un'annotazione ha più argomenti di quelli consentiti; gli argomenti superflui sono ignorati.
+
+
+ I riferimenti impliciti ai membri della cartella di lavoro all'interno di un documento del modulo della cartella di lavoro possono essere errori per i riferimenti impliciti alla cartella di lavoro attiva, che è il comportamento in tutti gli altri moduli. Qualificando esplicitamente queste chiamate dei membri con Me, l'ambiguità può essere risolta.
+
+
+ I riferimenti impliciti ai membri del foglio di lavoro all'interno di un documento del modulo del foglio di lavoro possono essere errori per i riferimenti impliciti al foglio di lavoro attivo, che è il comportamento in tutti gli altri moduli. Qualificando esplicitamente queste chiamate dei membri con Me, l'ambiguità può essere risolta.
+
+
+ L'ultimo parametro (il parametro 'Value') dei mutatori di proprietà è sempre passato da ByVal. Questo vale indipendentemente dalla presenza o assenza di un modificatore ByRef o ByVal. Eccezione: un UserDefinedType deve sempre essere passato ByRef anche quando è l'ultimo parametro di un mutatore di proprietà.È stata specificata un'annotazione in un modulo di un tipo che non è compatibile con tale annotazione. Alcune annotazioni possono essere utilizzate solo in un modulo di un tipo specifico; altre non possono essere utilizzate in moduli di determinati tipi.
@@ -460,15 +460,15 @@ Se il parametro può essere nullo, ignorare questo risultato dell'ispezione; il
Tutti gli argomenti di qualsiasi chiamata di funzione/procedura sono sempre valutati prima che la funzione sia invocata in modo che i rispettivi valori possano essere passati come parametri. Comunque, il comportamento della funzione IIf a volte viene frainteso credendo che SOLO l'espressione 'ParteVera' o SOLO l'espressione 'ParteFalsa' venga valutata in base al risultato della prima espressione di argomento. Di conseguenza, la funzione IIf può essere una fonte di effetti collaterali ed errori imprevisti se l'utente non tiene conto del fatto che entrambi gli argomenti ParteVera e ParteFalsa sono sempre valutati.
-
- MSForms espone i controlli UserForm come campi pubblici; l'accesso a questi campi al di fuori della classe UserForm rompe l'incapsulamento e accoppia inutilmente il codice a controlli su maschera specifici. Considerare di incapsulare i valori desiderati nella propria classe 'modello', facendo in modo che i gestori di eventi nella maschera manipolino queste proprietà del 'modello' e quindi il codice chiamante possa interrogare questo stato incapsulato invece di interrogare i controlli della maschera.
-
In generale, l'editor VBE rileva questo tipo di errore e non compila. Tuttavia, esistono alcuni scenari in cui l'errore è ignorato dal compilatore ed è generato un errore in fase di esecuzione. Per evitare un errore durante l'esecuzione, implementare la Proprietà o la Subroutine mancante. Sebbene un'istanza predefinita potrebbe essere intenzionale, è una fonte comune di bug e dovrebbe essere evitata. Utilizza il qualificatore 'Me' per fare riferimento esplicitamente all'istanza corrente ed eliminare qualsiasi ambiguità.
+
+ MSForms espone i controlli UserForm come campi pubblici; l'accesso a questi campi al di fuori della classe UserForm rompe l'incapsulamento e accoppia inutilmente il codice a controlli su maschera specifici. Considerare di incapsulare i valori desiderati nella propria classe 'modello', facendo in modo che i gestori di eventi nella maschera manipolino queste proprietà del 'modello' e quindi il codice chiamante possa interrogare questo stato incapsulato invece di interrogare i controlli della maschera.
+
La copia di un foglio di lavoro che contiene una dichiarazione Enum pubblica creerà anche una copia della dichiarazione Enum. La dichiarazione copiata provocherà un errore del compilatore "Nome ambiguo rilevato". La dichiarazione di enumerazioni nei moduli Standard o di Classe evita la duplicazione involontaria di una dichiarazione Enum.
diff --git a/Rubberduck.Resources/Inspections/InspectionInfo.resx b/Rubberduck.Resources/Inspections/InspectionInfo.resx
index c48abd29e3..5fcd9f4bb1 100644
--- a/Rubberduck.Resources/Inspections/InspectionInfo.resx
+++ b/Rubberduck.Resources/Inspections/InspectionInfo.resx
@@ -478,4 +478,13 @@ If the parameter can be null, ignore this inspection result; passing a null valu
The default (Public) interface of a class module should not expose the implementation of other interfaces or event handler procedures.
+
+ Arrays created with a VBA.Array function call explicitly qualified with the 'VBA' library are always zero-based, regardless of Option Base 1.
+
+
+ Arrays created with ParamArray are always zero-based, regardless of Option Base 1.
+
+
+ Get-only property 'Range.Cells' accepts two optional parameters, but if none is supplied then it simply yields a reference to the parent 'Range' object, which makes it entirely redundant.
+
\ No newline at end of file
diff --git a/Rubberduck.Resources/Inspections/InspectionNames.Designer.cs b/Rubberduck.Resources/Inspections/InspectionNames.Designer.cs
index 7b24516203..f91d7b6b48 100644
--- a/Rubberduck.Resources/Inspections/InspectionNames.Designer.cs
+++ b/Rubberduck.Resources/Inspections/InspectionNames.Designer.cs
@@ -19,7 +19,7 @@ namespace Rubberduck.Resources.Inspections {
// class via a tool like ResGen or Visual Studio.
// To add or remove a member, edit your .ResX file then rerun ResGen
// with the /str option, or rebuild your VS project.
- [global::System.CodeDom.Compiler.GeneratedCodeAttribute("System.Resources.Tools.StronglyTypedResourceBuilder", "16.0.0.0")]
+ [global::System.CodeDom.Compiler.GeneratedCodeAttribute("System.Resources.Tools.StronglyTypedResourceBuilder", "17.0.0.0")]
[global::System.Diagnostics.DebuggerNonUserCodeAttribute()]
[global::System.Runtime.CompilerServices.CompilerGeneratedAttribute()]
public class InspectionNames {
@@ -438,6 +438,24 @@ public static string ImplicitVariantReturnTypeInspection {
}
}
+ ///
+ /// Looks up a localized string similar to Inconsistently zero-based array.
+ ///
+ public static string InconsistentArrayBaseInspection {
+ get {
+ return ResourceManager.GetString("InconsistentArrayBaseInspection", resourceCulture);
+ }
+ }
+
+ ///
+ /// Looks up a localized string similar to Inconsistently zero-based parameter array.
+ ///
+ public static string InconsistentParamArrayBaseInspection {
+ get {
+ return ResourceManager.GetString("InconsistentParamArrayBaseInspection", resourceCulture);
+ }
+ }
+
///
/// Looks up a localized string similar to Indexed default member access.
///
@@ -807,6 +825,15 @@ public static string ParameterCanBeByValInspection {
}
}
+ ///
+ /// Looks up a localized string similar to Parameterless call to 'Range.Cells' is redundant.
+ ///
+ public static string ParameterlessCellsInspection {
+ get {
+ return ResourceManager.GetString("ParameterlessCellsInspection", resourceCulture);
+ }
+ }
+
///
/// Looks up a localized string similar to Parameter is not used..
///
diff --git a/Rubberduck.Resources/Inspections/InspectionNames.fr.resx b/Rubberduck.Resources/Inspections/InspectionNames.fr.resx
index 19720eba87..c2cba744ba 100644
--- a/Rubberduck.Resources/Inspections/InspectionNames.fr.resx
+++ b/Rubberduck.Resources/Inspections/InspectionNames.fr.resx
@@ -135,6 +135,9 @@
Référence implicite au classeur actif
+
+ Paramètre ByRef implicite
+
Membre implicitement public
@@ -201,59 +204,71 @@
La variable objet est assignée lors de sa déclaration.
+
+ La valeur renvoyée par la fonction est systématiquement ignorée.
+
L'assignation d'une référence d'objet requiert le mot-clé 'Set'.
+
+ Paramètre d'annotation manquant
+
Utilisation du mot-clé 'Dim' au niveau moduleVariable non déclarée
-
- Paramètre d'annotation manquant
+
+ L'identifiant utilise la notation hongroise.
-
- Appel de fonction WorksheetFunction à liaison tardive.
+
+ Membre inexistant ou introuvableLes expressions spécifiques à l'application hôte, encadrées de crochets, sont seulement évaluées lors de l'exécution
-
- L'identifiant utilise la notation hongroise.
+
+ Appel de fonction WorksheetFunction à liaison tardive.
-
- Membre inexistant ou introuvable
+
+ 'Option Base 0' est redondant
-
- Utilisation d'un entier 16-bits
+
+ Annotation invalide
-
- Bloc 'Case' vide
+
+ Attribut manquantBranche conditionelle vide
+
+ Option de module redondante
+
Modificateur 'ByRef' redondant
-
- 'Option Base 0' est redondant
+
+ Bloc 'Else' vide
-
- Boucle 'For...Next' vide
+
+ Utilisation d'un entier 16-bits
-
- Paramètre ByRef implicite
+
+ Mot-clé 'Stop'
-
- Boucle 'For Each...Next' vide
+
+ Bloc 'Case' videBoucle 'Do...While' vide
-
- Bloc 'Else' vide
+
+ Boucle 'For Each...Next' vide
+
+
+ Boucle 'For...Next' videBoucle 'While...Wend' vide
@@ -261,15 +276,6 @@
Déclaration cachée
-
- Attribut manquant
-
-
- Option de module redondante
-
-
- Mot-clé 'Stop'
-
Assignation d'une valeur Booléenne littérale dans une structure conditionnelle
@@ -297,17 +303,20 @@
Une feuille Excel accessible statiquement est référencée par une chaîne de caractères
-
- Assignation non utilisée
+
+ Utilisation d'un membre marqué '@Obsolete'
+
+
+ Utilisation de la convention d'appel 'CDecl' sous WindowsAnnotation dupliquée
-
- Accès à un membre pouvant renvoyer 'Nothing'
+
+ Module sans annotation '@Folder'
-
- Une fonction est cachée par une référence de cellule valide
+
+ Instruction obsolète 'On Local Error'Utilisation inappropriée ou incorrecte de la fonction 'IsMissing'
@@ -315,21 +324,18 @@
Utilisation inappropriée ou incorrecte de la fonction 'IsMissing'
-
- Module sans annotation '@Folder'
-
-
- Utilisation de la convention d'appel 'CDecl' sous Windows
-
-
- Utilisation d'un membre marqué '@Obsolete'
-
-
- Instruction obsolète 'On Local Error'
+
+ Assignation non utiliséeCaractère de soulignement dans le nom d'un membre d'un module de classe
+
+ Accès à un membre pouvant renvoyer 'Nothing'
+
+
+ Une fonction est cachée par une référence de cellule valide
+
La valeur de l'attribut diffère de celle suggérée par l'annotation
@@ -339,6 +345,18 @@
Annotation manquante (module)
+
+ Mot-clé utilisé comme nom de membre
+
+
+ Marqueur de continuation entre les mots-clés
+
+
+ Identifiant contenant un espace insécable ( )
+
+
+ Numéro de ligne négatif
+
Utilisation de l'instruction obsolète 'While...Wend'
@@ -396,46 +414,37 @@
Assignation 'Let' suspecte
-
- La valeur renvoyée par la fonction est systématiquement ignorée.
-
La valeur renvoyée par la fonction est ignorée.Constante implicitement typée
-
- Mot-clé utilisé comme nom de membre
-
-
- Marqueur de continuation entre les mots-clés
-
-
- Numéro de ligne négatif
-
-
- Identifiant contenant un espace insécable ( )
-
Arguments d'annotation superflus
-
- Annotation dans un type de composant incompatible
-
-
- Référence implicite au classeur contenant le projet
-
Référence implicite à la feuille (Worksheet) hôte
-
- Annotation invalide
+
+ Référence implicite au classeur contenant le projetModificateur ByRef trompeur
+
+ Annotation dans un type de composant incompatible
+
Annotation inconnue
+
+ Tableau a zéro pour base
+
+
+ ParamArray a zéro pour base
+
+
+ L'appel non paramétré à 'Range.Cells' est redondant
+
\ No newline at end of file
diff --git a/Rubberduck.Resources/Inspections/InspectionNames.resx b/Rubberduck.Resources/Inspections/InspectionNames.resx
index 794b939ab1..bde0984c00 100644
--- a/Rubberduck.Resources/Inspections/InspectionNames.resx
+++ b/Rubberduck.Resources/Inspections/InspectionNames.resx
@@ -478,4 +478,13 @@
Implementations of interfaces and event handlers should be Private
+
+ Inconsistently zero-based array
+
+
+ Inconsistently zero-based parameter array
+
+
+ Parameterless call to 'Range.Cells' is redundant
+
\ No newline at end of file
diff --git a/Rubberduck.Resources/Inspections/InspectionResults.Designer.cs b/Rubberduck.Resources/Inspections/InspectionResults.Designer.cs
index aeedd681d5..8f6a703a6c 100644
--- a/Rubberduck.Resources/Inspections/InspectionResults.Designer.cs
+++ b/Rubberduck.Resources/Inspections/InspectionResults.Designer.cs
@@ -19,7 +19,7 @@ namespace Rubberduck.Resources.Inspections {
// class via a tool like ResGen or Visual Studio.
// To add or remove a member, edit your .ResX file then rerun ResGen
// with the /str option, or rebuild your VS project.
- [global::System.CodeDom.Compiler.GeneratedCodeAttribute("System.Resources.Tools.StronglyTypedResourceBuilder", "16.0.0.0")]
+ [global::System.CodeDom.Compiler.GeneratedCodeAttribute("System.Resources.Tools.StronglyTypedResourceBuilder", "17.0.0.0")]
[global::System.Diagnostics.DebuggerNonUserCodeAttribute()]
[global::System.Runtime.CompilerServices.CompilerGeneratedAttribute()]
public class InspectionResults {
@@ -447,6 +447,24 @@ public static string ImplicitVariantReturnTypeInspection {
}
}
+ ///
+ /// Looks up a localized string similar to This array is inconsistently zero-based.
+ ///
+ public static string InconsistentArrayBaseInspection {
+ get {
+ return ResourceManager.GetString("InconsistentArrayBaseInspection", resourceCulture);
+ }
+ }
+
+ ///
+ /// Looks up a localized string similar to ParamArray '{0}' is inconsistently zero-based.
+ ///
+ public static string InconsistentParamArrayBaseInspection {
+ get {
+ return ResourceManager.GetString("InconsistentParamArrayBaseInspection", resourceCulture);
+ }
+ }
+
///
/// Looks up a localized string similar to The expression '{0}' contains an indexed default member access to '{1}'..
///
@@ -843,6 +861,15 @@ public static string ParameterCanBeByValInspection {
}
}
+ ///
+ /// Looks up a localized string similar to Parameterless 'Range.Cells' call is redundant..
+ ///
+ public static string ParameterlessCellsInspection {
+ get {
+ return ResourceManager.GetString("ParameterlessCellsInspection", resourceCulture);
+ }
+ }
+
///
/// Looks up a localized string similar to Parameter '{0}' is not used..
///
diff --git a/Rubberduck.Resources/Inspections/InspectionResults.fr.resx b/Rubberduck.Resources/Inspections/InspectionResults.fr.resx
index 08b5e68c04..5f1739897f 100644
--- a/Rubberduck.Resources/Inspections/InspectionResults.fr.resx
+++ b/Rubberduck.Resources/Inspections/InspectionResults.fr.resx
@@ -117,6 +117,9 @@
System.Resources.ResXResourceWriter, System.Windows.Forms, Version=4.0.0.0, Culture=neutral, PublicKeyToken=b77a5c561934e089
+
+ Préférez 'vbNullString' à une chaîne de caractères vide.
+
Le champ public '{0}' rompt l'encapsulation.
@@ -137,12 +140,18 @@
La variable '{0}' est assignée lors de sa déclaration.
+
+ La valeur renvoyée par la fonction '{0}' n'est jamais utilisée.
+
Le paramètre '{0}' passé par valeur est assigné.{0} '{1}' n'est pas utilisé(e).
+
+ Le paramètre '{0}' est passé implicitement par référence.
+
Le membre '{0}' est implicitement public.
@@ -176,45 +185,45 @@
La variable '{0}' n'est jamais assignée.
-
- Préférez 'vbNullString' à une chaîne de caractères vide.
-
La variable '{0}' est assignée dans le mot-clé 'Set'.
-
- Le membre '{0}' réfère implicitement au classeur actif.
-
-
- L'instruction comporte plusieurs déclarations.
-
-
- {0} '{1}' est implicitement de type 'Variant'.
-
Le projet '{0}' n'est pas nommé.L'assignation utilise le mot-clé obsolète 'Call'.
+
+ Le commentaire utilise la forme obsolète 'Rem'.
+
L'assignation utilise le mot-clé obsolète 'Let'.
-
- Le module '{0}' utilise 'Option Base 1'.
+
+ Le membre '{0}' réfère implicitement à la feuille active.
-
- Le commentaire utilise la forme obsolète 'Rem'.
+
+ Le membre '{0}' réfère implicitement au classeur actif.
+
+
+ L'instruction comporte plusieurs déclarations.{0} de {1} '{2}' utilise un indicateur de type.
-
- Le membre '{0}' réfère implicitement à la feuille active.
+
+ Le module '{0}' utilise 'Option Base 1'.Remplacer la fonction '{0}' par la fonction typée équivalente.
+
+ {0} '{1}' est implicitement de type 'Variant'.
+
+
+ Un paramètre était attendu dans l'annotation '{0}'.
+
La variable module '{0}' est déclarée avec le mot-clé 'Dim'.
@@ -222,71 +231,68 @@
La variable locale '{0}' n'est pas déclarée.{0} variable name
-
- Un paramètre était attendu dans l'annotation '{0}'.
-
{0} ({1} résultats)
-
- Utilisation du membre à liaison tardive Application.{0}.
+
+ Le membre '{0}' n'est pas exposé par l'interface du type '{1}'.L'espression '{0}' ne peut être validée lors de la compilation.
-
- Le membre '{0}' n'est pas exposé par l'interface du type '{1}'.
-
-
- Un bloc 'Case' ne contient aucune instruction exécutable.
+
+ Utilisation du membre à liaison tardive Application.{0}.
-
- Le paramètre '{0}' est passé implicitement par référence.
+
+ Le module '{0}' spécifie 'Option Base 0'.
-
- L'étiquette de ligne '{0}' n'est pas utilisée.
+
+ Annotation '{0}' invalide dans ce contexte.
-
- Le mot-clé 'Stop' halte l'exécution.
+
+ Le module ou membre '{0}' a l'annotation '{1}', mais pas l'attribut correspondant.
-
- {0} '{1}' cache {2} '{3}'.
+
+ Bloc 'If' n'exécute aucune instruction.
-
- Une erreur d'exécution est générée à l'aide de l'instruction obsolète 'Error'.
+
+ '{0}' n'a aucun effet.Le paramètre '{0}' a un modificateur 'ByRef' redondant.
-
- Boucle 'For Each...Next' n'exécute aucune instruction.
+
+ L'étiquette de ligne '{0}' n'est pas utilisée.Bloc 'Else' n'exécute aucune instruction.
-
- Boucle 'For...Next' n'exécute aucune instruction.
-
{0} '{1}' est déclarée 'As Integer'.
-
- Boucle 'While...Wend' n'exécute aucune instruction.
-
-
- Bloc 'If' n'exécute aucune instruction.
+
+ Le mot-clé 'Stop' halte l'exécution.
-
- Le module '{0}' spécifie 'Option Base 0'.
+
+ Un bloc 'Case' ne contient aucune instruction exécutable.Une boucle 'Do...While' vide, qui ne contient aucune instruction exécutable, laisse songeur quant aux intentions de l'auteur. Évitez d'écrire du code qui n'a pas besoin d'être écrit.
-
- '{0}' n'a aucun effet.
+
+ Boucle 'For Each...Next' n'exécute aucune instruction.
-
- Le module ou membre '{0}' a l'annotation '{1}', mais pas l'attribut correspondant.
+
+ Boucle 'For...Next' n'exécute aucune instruction.
+
+
+ Boucle 'While...Wend' n'exécute aucune instruction.
+
+
+ {0} '{1}' cache {2} '{3}'.
+
+
+ Une erreur d'exécution est générée à l'aide de l'instruction obsolète 'Error'.Valeur Booléenne littérale '{0}' assignée dans une structure conditionnelle
@@ -294,6 +300,18 @@
Le module/classe {0} est vide.
+
+ Le bloc sous la condition '{0}' est inatteignable.
+
+
+ Le bloc 'Case Else' est inatteignable.
+
+
+ L'expression du bloc 'Case' causera une erreur d'exécution 13 (type mismatch).
+
+
+ Le bloc 'Case' est inatteignable.
+
La gestion d'erreurs est désactivée sans être réactivée.
@@ -309,17 +327,26 @@
Une feuille Excel accessible statiquement peut être référée en utilisant son nom de code.
-
- Une assignation est écrasée par une assignation subséquente, ou la valeur assignée n'est jamais utilisée.
+
+ Considérez remplacer l'appel par '{0}'.{1}
+
+
+ '{0}' est déclarée avec la convention d'appel 'CDecl'.
+
+
+ Les plages de valeurs d'un bloc 'Case' doivent être exprimés sous la forme '[x] To [y]', où [x] est plus petit ou égal à [y].
+
+
+ L'expression du bloc 'Case' causera une erreur d'exécution 6 (overflow).L'annotation '{0}' est dupliquée.
-
- Le résultat de l'appel à '{0}' n'est pas testé pour 'Nothing'.
+
+ Le module '{0}' n'a pas d'annotation '@Folder'.
-
- '{0}' est cachée par une référence à une cellule valide.
+
+ Instruction 'On Local Error' détectée.'IsMissing' sera toujours 'False' avec ce paramètre.
@@ -327,21 +354,18 @@
'IsMissing' reçoit une expression qui n'est pas l'un des paramètres de la procédure.
-
- Le module '{0}' n'a pas d'annotation '@Folder'.
-
-
- '{0}' est déclarée avec la convention d'appel 'CDecl'.
-
-
- Considérez remplacer l'appel par '{0}'.{1}
-
-
- Instruction 'On Local Error' détectée.
+
+ Une assignation est écrasée par une assignation subséquente, ou la valeur assignée n'est jamais utilisée.Le nom du membre public '{0}' contient un caractère de soulignement.
+
+ Le résultat de l'appel à '{0}' n'est pas testé pour 'Nothing'.
+
+
+ '{0}' est cachée par une référence à une cellule valide.
+
La valeur de l'attribut {0} ({1}) est désynchronisée avec l'annotation {2}.
@@ -351,14 +375,14 @@
Le module '{0}' a l'attribut '{1}' avec la/les valeur(s) '{2}', mais aucune annotation correspondante.
+
+ Le nom du membre '{0}' est un mot-clé.
+
Marqueur(s) de continuation inattendu.
-
- Utilisation de 'On Error GoTo -1'
-
-
- Utilisation d'un numéro de ligne négatif
+
+ L'identifiant '{0}' comporte un espace insécable.{0}
@@ -366,33 +390,15 @@ Andrew "ThunderFrame" Jackson serait fier!
Vous voyez ce résultat d'inspection parce qu'il n'y a aucune raison que ce soit du vrai code et que vous tentez simplement de pousser les limites des capacités d'analyse de Rubberduck... n'est-ce pas? N'EST-CE PAS?
In memoriam, 1972-2018
-
- L'identifiant '{0}' comporte un espace insécable.
+
+