From 0b93e503e275ab27fb77569192cd371c7f6099cd Mon Sep 17 00:00:00 2001 From: comintern Date: Sat, 3 Nov 2018 16:36:23 -0500 Subject: [PATCH 1/3] Add new inspection for Excel UDFs hidden by cells. --- ...elUdfNameIsValidCellReferenceInspection.cs | 49 ++++++ .../QuickFixes/RenameDeclarationQuickFix.cs | 6 +- Rubberduck.Core/Properties/Settings.settings | 27 +-- Rubberduck.Core/app.config | 28 +--- .../Inspections/InspectionInfo.Designer.cs | 9 + .../Inspections/InspectionInfo.resx | 3 + .../Inspections/InspectionNames.Designer.cs | 9 + .../Inspections/InspectionNames.resx | 3 + .../Inspections/InspectionResults.Designer.cs | 9 + .../Inspections/InspectionResults.resx | 4 + .../Rubberduck.Resources.csproj | 16 +- .../Settings/AutoCompletesPage.Designer.cs | 158 ++++-------------- .../Settings/SettingsUI.Designer.cs | 9 - ...NameIsValidCellReferenceInspectionTests.cs | 128 ++++++++++++++ 14 files changed, 279 insertions(+), 179 deletions(-) create mode 100644 Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelUdfNameIsValidCellReferenceInspection.cs create mode 100644 RubberduckTests/Inspections/ExcelUdfNameIsValidCellReferenceInspectionTests.cs diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelUdfNameIsValidCellReferenceInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelUdfNameIsValidCellReferenceInspection.cs new file mode 100644 index 0000000000..f23b890678 --- /dev/null +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ExcelUdfNameIsValidCellReferenceInspection.cs @@ -0,0 +1,49 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text.RegularExpressions; +using Rubberduck.Inspections.Abstract; +using Rubberduck.Inspections.Results; +using Rubberduck.Parsing.Inspections; +using Rubberduck.Parsing.Inspections.Abstract; +using Rubberduck.Parsing.Symbols; +using Rubberduck.Parsing.VBA; +using Rubberduck.Resources.Inspections; + +namespace Rubberduck.Inspections.Inspections.Concrete +{ + [RequiredLibrary("Excel")] + public class ExcelUdfNameIsValidCellReferenceInspection : InspectionBase + { + public ExcelUdfNameIsValidCellReferenceInspection(RubberduckParserState state) : base(state) { } + + private static readonly Regex ValidCellIdRegex = + new Regex(@"^([a-z]|[a-z]{2}|[a-w][a-z]{2}|x([a-e][a-z]|f[a-d]))(?\d+)$", + RegexOptions.Compiled | RegexOptions.IgnoreCase | RegexOptions.ExplicitCapture); + + private static readonly HashSet VisibleAsUdf = new HashSet { Accessibility.Public, Accessibility.Implicit }; + + private const uint MaximumExcelRows = 1048576; + + protected override IEnumerable DoGetInspectionResults() + { + var excel = State.DeclarationFinder.Projects.SingleOrDefault(item => !item.IsUserDefined && item.IdentifierName == "Excel"); + if (excel == null) + { + return Enumerable.Empty(); + } + + var candidates = UserDeclarations.OfType().Where(decl => + decl.ParentScopeDeclaration.DeclarationType == DeclarationType.ProceduralModule && + VisibleAsUdf.Contains(decl.Accessibility)); + + return (from function in candidates.Where(decl => ValidCellIdRegex.IsMatch(decl.IdentifierName)) + let row = Convert.ToUInt32(ValidCellIdRegex.Matches(function.IdentifierName)[0].Groups["Row"].Value) + where row > 0 && row <= MaximumExcelRows && !IsIgnoringInspectionResultFor(function, AnnotationName) + select new DeclarationInspectionResult(this, + string.Format(InspectionResults.ExcelUdfNameIsValidCellReferenceInspection, function.IdentifierName), + function)) + .Cast().ToList(); + } + } +} diff --git a/Rubberduck.CodeAnalysis/QuickFixes/RenameDeclarationQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/RenameDeclarationQuickFix.cs index ab6c2817a8..e7a308d5af 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/RenameDeclarationQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/RenameDeclarationQuickFix.cs @@ -1,6 +1,7 @@ using System.Globalization; using Rubberduck.Inspections.Abstract; using Rubberduck.Inspections.Concrete; +using Rubberduck.Inspections.Inspections.Concrete; using Rubberduck.Interaction; using Rubberduck.Parsing.Inspections.Abstract; using Rubberduck.Parsing.VBA; @@ -18,7 +19,10 @@ public sealed class RenameDeclarationQuickFix : QuickFixBase private readonly IMessageBox _messageBox; public RenameDeclarationQuickFix(IVBE vbe, RubberduckParserState state, IMessageBox messageBox) - : base(typeof(HungarianNotationInspection), typeof(UseMeaningfulNameInspection), typeof(DefaultProjectNameInspection)) + : base(typeof(HungarianNotationInspection), + typeof(UseMeaningfulNameInspection), + typeof(DefaultProjectNameInspection), + typeof(ExcelUdfNameIsValidCellReferenceInspection)) { _vbe = vbe; _state = state; diff --git a/Rubberduck.Core/Properties/Settings.settings b/Rubberduck.Core/Properties/Settings.settings index 65cc1ca0f3..1962a7e622 100644 --- a/Rubberduck.Core/Properties/Settings.settings +++ b/Rubberduck.Core/Properties/Settings.settings @@ -268,26 +268,13 @@ <?xml version="1.0" encoding="utf-16"?> -<AutoCompleteSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema" IsEnabled="false" CompleteBlockOnTab="true" CompleteBlockOnEnter="true" EnableSmartConcat="true"> - <AutoCompletes> - <AutoComplete Key="AutoCompleteClosingBrace" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteClosingBracket" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteClosingParenthese" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteClosingString" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteDoBlock" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteEnumBlock" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteForBlock" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteFunctionBlock" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteIfBlock" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteOnErrorResumeNextBlock" IsEnabled="true" /> - <AutoComplete Key="AutoCompletePrecompilerIfBlock" IsEnabled="true" /> - <AutoComplete Key="AutoCompletePropertyBlock" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteSelectBlock" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteSubBlock" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteTypeBlock" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteWhileBlock" IsEnabled="true" /> - <AutoComplete Key="AutoCompleteWithBlock" IsEnabled="true" /> - </AutoCompletes> +<AutoCompleteSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema" IsEnabled="false"> + <SmartConcat> + <IsEnabled>false</IsEnabled> + <ConcatVbNewLineModifier>None</ConcatVbNewLineModifier> + </SmartConcat> + <SelfClosingPairs IsEnabled="false" /> + <BlockCompletion IsEnabled="false" CompleteOnEnter="false" CompleteOnTab="false" /> </AutoCompleteSettings> diff --git a/Rubberduck.Core/app.config b/Rubberduck.Core/app.config index 3aef405463..11c717c6c1 100644 --- a/Rubberduck.Core/app.config +++ b/Rubberduck.Core/app.config @@ -395,27 +395,13 @@ - - - - - - - - - - - - - - - - - - - + xmlns:xsd="http://www.w3.org/2001/XMLSchema" IsEnabled="false"> + + false + None + + + diff --git a/Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs b/Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs index e399928601..e98d337132 100644 --- a/Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs +++ b/Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs @@ -222,6 +222,15 @@ public static string EncapsulatePublicFieldInspection { } } + /// + /// Looks up a localized string similar to Functions that are visible to Excel as User-Defined Functions will return a '#REF' error when used on a Worksheet if they match the name of a valid cell reference. If the function is intended to be used as a UDF, it must be renamed. If the function is not intended to be used as a UDF, it should be scoped as 'Private' or moved out of a standard Module.. + /// + public static string ExcelUdfNameIsValidCellReferenceInspection { + get { + return ResourceManager.GetString("ExcelUdfNameIsValidCellReferenceInspection", resourceCulture); + } + } + /// /// Looks up a localized string similar to A member is written as a function, but used as a procedure. Unless the function is recursive, consider converting the 'Function' into a 'Sub'. If the function is recursive, none of its external callers are using the returned value.. /// diff --git a/Rubberduck.Resources/Inspections/InspectionInfo.resx b/Rubberduck.Resources/Inspections/InspectionInfo.resx index b06e89193b..58c4817d84 100644 --- a/Rubberduck.Resources/Inspections/InspectionInfo.resx +++ b/Rubberduck.Resources/Inspections/InspectionInfo.resx @@ -349,4 +349,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu An assignment is immediately overridden by another assignment or is never referenced. + + Functions that are visible to Excel as User-Defined Functions will return a '#REF' error when used on a Worksheet if they match the name of a valid cell reference. If the function is intended to be used as a UDF, it must be renamed. If the function is not intended to be used as a UDF, it should be scoped as 'Private' or moved out of a standard Module. + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/InspectionNames.Designer.cs b/Rubberduck.Resources/Inspections/InspectionNames.Designer.cs index f13cc181ab..def9778047 100644 --- a/Rubberduck.Resources/Inspections/InspectionNames.Designer.cs +++ b/Rubberduck.Resources/Inspections/InspectionNames.Designer.cs @@ -222,6 +222,15 @@ public static string EncapsulatePublicFieldInspection { } } + /// + /// Looks up a localized string similar to Function is hidden by Excel cell reference. + /// + public static string ExcelUdfNameIsValidCellReferenceInspection { + get { + return ResourceManager.GetString("ExcelUdfNameIsValidCellReferenceInspection", resourceCulture); + } + } + /// /// Looks up a localized string similar to Function return value is never used. /// diff --git a/Rubberduck.Resources/Inspections/InspectionNames.resx b/Rubberduck.Resources/Inspections/InspectionNames.resx index 619f5ddbb9..cf1ef9d7d4 100644 --- a/Rubberduck.Resources/Inspections/InspectionNames.resx +++ b/Rubberduck.Resources/Inspections/InspectionNames.resx @@ -348,4 +348,7 @@ Assignment is not used + + Function is hidden by Excel cell reference + \ No newline at end of file diff --git a/Rubberduck.Resources/Inspections/InspectionResults.Designer.cs b/Rubberduck.Resources/Inspections/InspectionResults.Designer.cs index 02946f951a..7403434027 100644 --- a/Rubberduck.Resources/Inspections/InspectionResults.Designer.cs +++ b/Rubberduck.Resources/Inspections/InspectionResults.Designer.cs @@ -222,6 +222,15 @@ public static string EncapsulatePublicFieldInspection { } } + /// + /// Looks up a localized string similar to '{0}' is hidden by a valid Excel cell reference.. + /// + public static string ExcelUdfNameIsValidCellReferenceInspection { + get { + return ResourceManager.GetString("ExcelUdfNameIsValidCellReferenceInspection", resourceCulture); + } + } + /// /// Looks up a localized string similar to Return value of function '{0}' is never used.. /// diff --git a/Rubberduck.Resources/Inspections/InspectionResults.resx b/Rubberduck.Resources/Inspections/InspectionResults.resx index 36ac7d58cb..4074833183 100644 --- a/Rubberduck.Resources/Inspections/InspectionResults.resx +++ b/Rubberduck.Resources/Inspections/InspectionResults.resx @@ -378,4 +378,8 @@ An assignment is immediately overridden by another assignment or is never referenced. + + '{0}' is hidden by a valid Excel cell reference. + {0} Function name + \ No newline at end of file diff --git a/Rubberduck.Resources/Rubberduck.Resources.csproj b/Rubberduck.Resources/Rubberduck.Resources.csproj index 88e5eb41a0..7205ec5764 100644 --- a/Rubberduck.Resources/Rubberduck.Resources.csproj +++ b/Rubberduck.Resources/Rubberduck.Resources.csproj @@ -12,12 +12,20 @@ - - PublicResXFileCodeGenerator - $([System.String]::Copy('%(FileName)')).Designer.cs - + + + + True + True $([System.String]::Copy('%(Filename)').Replace('.Designer', '')).resx + + + + PublicResXFileCodeGenerator + $([System.String]::Copy('%(FileName)')).Designer.cs + + \ No newline at end of file diff --git a/Rubberduck.Resources/Settings/AutoCompletesPage.Designer.cs b/Rubberduck.Resources/Settings/AutoCompletesPage.Designer.cs index e71b292377..18a7c254a2 100644 --- a/Rubberduck.Resources/Settings/AutoCompletesPage.Designer.cs +++ b/Rubberduck.Resources/Settings/AutoCompletesPage.Designer.cs @@ -61,160 +61,70 @@ internal AutoCompletesPage() { } /// - /// Looks up a localized string similar to Close curly braces '{'. + /// Looks up a localized string similar to Block Completion. /// - public static string AutoCompleteClosingBraceDescription { + public static string BlockCompletion { get { - return ResourceManager.GetString("AutoCompleteClosingBraceDescription", resourceCulture); + return ResourceManager.GetString("BlockCompletion", resourceCulture); } } /// - /// Looks up a localized string similar to Close square brackets '['. - /// - public static string AutoCompleteClosingBracketDescription { - get { - return ResourceManager.GetString("AutoCompleteClosingBracketDescription", resourceCulture); - } - } - - /// - /// Looks up a localized string similar to Close parentheses '('. - /// - public static string AutoCompleteClosingParentheseDescription { - get { - return ResourceManager.GetString("AutoCompleteClosingParentheseDescription", resourceCulture); - } - } - - /// - /// Looks up a localized string similar to Close string literals '"'. - /// - public static string AutoCompleteClosingStringDescription { - get { - return ResourceManager.GetString("AutoCompleteClosingStringDescription", resourceCulture); - } - } - - /// - /// Looks up a localized string similar to Close 'Do [Until|While]...Loop' loop blocks. - /// - public static string AutoCompleteDoBlockDescription { - get { - return ResourceManager.GetString("AutoCompleteDoBlockDescription", resourceCulture); - } - } - - /// - /// Looks up a localized string similar to Close 'Enum' blocks. - /// - public static string AutoCompleteEnumBlockDescription { - get { - return ResourceManager.GetString("AutoCompleteEnumBlockDescription", resourceCulture); - } - } - - /// - /// Looks up a localized string similar to Close 'For [Each]...Next' loop blocks. - /// - public static string AutoCompleteForBlockDescription { - get { - return ResourceManager.GetString("AutoCompleteForBlockDescription", resourceCulture); - } - } - - /// - /// Looks up a localized string similar to Override 'Function' member block completion. - /// - public static string AutoCompleteFunctionBlockDescription { - get { - return ResourceManager.GetString("AutoCompleteFunctionBlockDescription", resourceCulture); - } - } - - /// - /// Looks up a localized string similar to Close 'If' blocks. - /// - public static string AutoCompleteIfBlockDescription { - get { - return ResourceManager.GetString("AutoCompleteIfBlockDescription", resourceCulture); - } - } - - /// - /// Looks up a localized string similar to Treat 'On Error Resume Next...GoTo 0' as a block. - /// - public static string AutoCompleteOnErrorResumeNextBlockDescription { - get { - return ResourceManager.GetString("AutoCompleteOnErrorResumeNextBlockDescription", resourceCulture); - } - } - - /// - /// Looks up a localized string similar to Close precompiler '#If' blocks. - /// - public static string AutoCompletePrecompilerIfBlockDescription { - get { - return ResourceManager.GetString("AutoCompletePrecompilerIfBlockDescription", resourceCulture); - } - } - - /// - /// Looks up a localized string similar to Override 'Property' member block completion. + /// Looks up a localized string similar to Autocomplete blocks on ENTER. /// - public static string AutoCompletePropertyBlockDescription { + public static string CompleteBlockOnEnter { get { - return ResourceManager.GetString("AutoCompletePropertyBlockDescription", resourceCulture); + return ResourceManager.GetString("CompleteBlockOnEnter", resourceCulture); } } /// - /// Looks up a localized string similar to Close 'Select' blocks. + /// Looks up a localized string similar to Autocomplete blocks on TAB. /// - public static string AutoCompleteSelectBlockDescription { + public static string CompleteBlockOnTab { get { - return ResourceManager.GetString("AutoCompleteSelectBlockDescription", resourceCulture); + return ResourceManager.GetString("CompleteBlockOnTab", resourceCulture); } } /// - /// Looks up a localized string similar to Override 'Sub' member block completion. + /// Looks up a localized string similar to Concatenate 'vbNewLine' on Ctrl+Enter. /// - public static string AutoCompleteSubBlockDescription { + public static string ConcatVbNewLine { get { - return ResourceManager.GetString("AutoCompleteSubBlockDescription", resourceCulture); + return ResourceManager.GetString("ConcatVbNewLine", resourceCulture); } } /// - /// Looks up a localized string similar to Close 'Type' blocks. + /// Looks up a localized string similar to Enable autocompletion features. /// - public static string AutoCompleteTypeBlockDescription { + public static string EnableAutocompleteLabel { get { - return ResourceManager.GetString("AutoCompleteTypeBlockDescription", resourceCulture); + return ResourceManager.GetString("EnableAutocompleteLabel", resourceCulture); } } /// - /// Looks up a localized string similar to Close 'While...Wend' loop blocks. + /// Looks up a localized string similar to Enable block completion. /// - public static string AutoCompleteWhileBlockDescription { + public static string EnableBlockCompletion { get { - return ResourceManager.GetString("AutoCompleteWhileBlockDescription", resourceCulture); + return ResourceManager.GetString("EnableBlockCompletion", resourceCulture); } } /// - /// Looks up a localized string similar to Close 'With' blocks. + /// Looks up a localized string similar to Enable self-closing pairs. /// - public static string AutoCompleteWithBlockDescription { + public static string EnableSelfClosingPairs { get { - return ResourceManager.GetString("AutoCompleteWithBlockDescription", resourceCulture); + return ResourceManager.GetString("EnableSelfClosingPairs", resourceCulture); } } /// - /// Looks up a localized string similar to Enable smart concatenation. + /// Looks up a localized string similar to Enable smart-concatenation. /// public static string EnableSmartConcat { get { @@ -223,38 +133,38 @@ public static string EnableSmartConcat { } /// - /// Looks up a localized string similar to Autocomplete blocks on ENTER. + /// Looks up a localized string similar to Autocompletion Settings. /// - public static string HandleEnterKey { + public static string PageHeader { get { - return ResourceManager.GetString("HandleEnterKey", resourceCulture); + return ResourceManager.GetString("PageHeader", resourceCulture); } } /// - /// Looks up a localized string similar to Autocomplete blocks on TAB. + /// Looks up a localized string similar to Configure which Rubberduck autocompletions are enabled.. /// - public static string HandleTabKey { + public static string PageInstructions { get { - return ResourceManager.GetString("HandleTabKey", resourceCulture); + return ResourceManager.GetString("PageInstructions", resourceCulture); } } /// - /// Looks up a localized string similar to Autocompletion Settings. + /// Looks up a localized string similar to Self-Closing Pairs. /// - public static string PageHeader { + public static string SelfClosingPairs { get { - return ResourceManager.GetString("PageHeader", resourceCulture); + return ResourceManager.GetString("SelfClosingPairs", resourceCulture); } } /// - /// Looks up a localized string similar to Configure which Rubberduck autocompletions are enabled.. + /// Looks up a localized string similar to Smart-Concatenation. /// - public static string PageInstructions { + public static string SmartConcat { get { - return ResourceManager.GetString("PageInstructions", resourceCulture); + return ResourceManager.GetString("SmartConcat", resourceCulture); } } } diff --git a/Rubberduck.Resources/Settings/SettingsUI.Designer.cs b/Rubberduck.Resources/Settings/SettingsUI.Designer.cs index e37a412e19..cb5cd64526 100644 --- a/Rubberduck.Resources/Settings/SettingsUI.Designer.cs +++ b/Rubberduck.Resources/Settings/SettingsUI.Designer.cs @@ -69,15 +69,6 @@ public static string ConfirmResetSettings { } } - /// - /// Looks up a localized string similar to Enable autocompletion. Feature isn't fully completed and may behave in unintended ways.. - /// - public static string EnableAutocompleteLabel { - get { - return ResourceManager.GetString("EnableAutocompleteLabel", resourceCulture); - } - } - /// /// Looks up a localized string similar to Export. /// diff --git a/RubberduckTests/Inspections/ExcelUdfNameIsValidCellReferenceInspectionTests.cs b/RubberduckTests/Inspections/ExcelUdfNameIsValidCellReferenceInspectionTests.cs new file mode 100644 index 0000000000..334b4e4c64 --- /dev/null +++ b/RubberduckTests/Inspections/ExcelUdfNameIsValidCellReferenceInspectionTests.cs @@ -0,0 +1,128 @@ +using System.Linq; +using System.Threading; +using NUnit.Framework; +using Rubberduck.Inspections.Inspections.Concrete; +using Rubberduck.VBEditor.SafeComWrappers; +using RubberduckTests.Mocks; + +namespace RubberduckTests.Inspections +{ + [TestFixture] + public class ExcelUdfNameIsValidCellReferenceInspectionTests + { + [TestCase("a1")] + [TestCase("A1")] + [TestCase("AA1")] + [TestCase("ZZ1")] + [TestCase("XFD1")] + [TestCase("XEZ1")] + [TestCase("WZZ1")] + [TestCase("Foo42")] + [TestCase("XFD1048576")] + [Category("Inspections")] + public void ExcelUdfNameIsValidCellReferenceInspection_ReturnsResult_ValidCells(string identifier) + { + const string codeTemplate = +@"Public Function {0}() As Long + {0} = 42 +End Function +"; + + Assert.AreEqual(1, InspectionResultCount(string.Format(codeTemplate, identifier), ComponentType.StandardModule)); + } + + [TestCase("Foo")] + [TestCase("XXX69")] + [TestCase("XKCD42")] + [TestCase("AAA1234567")] + [Category("Inspections")] + public void ExcelUdfNameIsValidCellReferenceInspection_ReturnsNoResult_InvalidAsCell(string identifier) + { + const string codeTemplate = +@"Public Function {0}() As Long + {0} = 42 +End Function +"; + + Assert.AreEqual(0, InspectionResultCount(string.Format(codeTemplate, identifier), ComponentType.StandardModule)); + } + + [TestCase(ComponentType.ClassModule)] + [TestCase(ComponentType.UserForm)] + [TestCase(ComponentType.DocObject)] + [Category("Inspections")] + public void ExcelUdfNameIsValidCellReferenceInspection_ReturnsNoResult_NonStandardModule(ComponentType moduleType) + { + const string code = +@"Public Function A1() As Long + A1 = 42 +End Function +"; + + Assert.AreEqual(0, InspectionResultCount(code, moduleType)); + } + + [Test] + [Category("Inspections")] + public void ExcelUdfNameIsValidCellReferenceInspection_ReturnsNoResult_Ignored() + { + const string code = +@"'@Ignore ExcelUdfNameIsValidCellReference +Public Function A1() As Long + A1 = 42 +End Function +"; + + Assert.AreEqual(0, InspectionResultCount(code, ComponentType.StandardModule)); + } + + [Test] + [Category("Inspections")] + public void ExcelUdfNameIsValidCellReferenceInspection_ReturnsNoResult_PrivateFunction() + { + const string code = +@"Private Function A1() As Long + A1 = 42 +End Function +"; + + Assert.AreEqual(0, InspectionResultCount(code, ComponentType.StandardModule)); + } + + [TestCase("Sub A1()", "Sub")] + [TestCase("Property Get A1() As Long", "Property")] + [TestCase("Property Let A1(foo As Long)", "Property")] + [TestCase("Property Set A1(foo As Variant)", "Property")] + [Category("Inspections")] + public void ExcelUdfNameIsValidCellReferenceInspection_ReturnsNoResult_NonFunction(string signature, string ending) + { + const string codeTemplate = +@"{0} + A1 = 42 +End {1} +"; + + Assert.AreEqual(0, InspectionResultCount(string.Format(codeTemplate, signature, ending), ComponentType.StandardModule)); + } + + private static int InspectionResultCount(string inputCode, ComponentType moduleType) + { + var builder = new MockVbeBuilder(); + var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected) + .AddComponent("UnderTest", moduleType, inputCode) + .AddReference("Excel", MockVbeBuilder.LibraryPathMsExcel, 1, 8, true) + .Build(); + + var vbe = builder.AddProject(project).Build(); + + using (var state = MockParser.CreateAndParse(vbe.Object)) + { + + var inspection = new ExcelUdfNameIsValidCellReferenceInspection(state); + var inspectionResults = inspection.GetInspectionResults(CancellationToken.None); + + return inspectionResults.Count(); + } + } + } +} From 62dfc3517bae8d599928b70055e3071d854d7393 Mon Sep 17 00:00:00 2001 From: comintern Date: Sun, 4 Nov 2018 16:00:06 -0600 Subject: [PATCH 2/3] Add inspection defaults to Settings.settings --- Rubberduck.Core/Properties/Settings.settings | 489 ++++++++++--------- Rubberduck.Core/Rubberduck.Core.csproj | 15 +- Rubberduck.Core/app.config | 2 + 3 files changed, 265 insertions(+), 241 deletions(-) diff --git a/Rubberduck.Core/Properties/Settings.settings b/Rubberduck.Core/Properties/Settings.settings index 1962a7e622..d061c65c55 100644 --- a/Rubberduck.Core/Properties/Settings.settings +++ b/Rubberduck.Core/Properties/Settings.settings @@ -3,279 +3,298 @@ - <?xml version="1.0" encoding="utf-16"?> -<HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <Key1>R</Key1> - <IsEnabled>true</IsEnabled> - <HasShiftModifier>true</HasShiftModifier> - <HasAltModifier>false</HasAltModifier> - <HasCtrlModifier>true</HasCtrlModifier> - <CommandTypeName>CodePaneRefactorRenameCommand</CommandTypeName> -</HotkeySetting> + + <HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <Key1>R</Key1> + <IsEnabled>true</IsEnabled> + <HasShiftModifier>true</HasShiftModifier> + <HasAltModifier>false</HasAltModifier> + <HasCtrlModifier>true</HasCtrlModifier> + <CommandTypeName>CodePaneRefactorRenameCommand</CommandTypeName> + </HotkeySetting> + - <?xml version="1.0" encoding="utf-16"?> -<HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <Key1>F</Key1> - <IsEnabled>true</IsEnabled> - <HasShiftModifier>true</HasShiftModifier> - <HasAltModifier>false</HasAltModifier> - <HasCtrlModifier>true</HasCtrlModifier> - <CommandTypeName>RefactorEncapsulateFieldCommand</CommandTypeName> -</HotkeySetting> + + <HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <Key1>F</Key1> + <IsEnabled>true</IsEnabled> + <HasShiftModifier>true</HasShiftModifier> + <HasAltModifier>false</HasAltModifier> + <HasCtrlModifier>true</HasCtrlModifier> + <CommandTypeName>RefactorEncapsulateFieldCommand</CommandTypeName> + </HotkeySetting> + - <?xml version="1.0" encoding="utf-16"?> -<HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <Key1>M</Key1> - <IsEnabled>true</IsEnabled> - <HasShiftModifier>true</HasShiftModifier> - <HasAltModifier>false</HasAltModifier> - <HasCtrlModifier>true</HasCtrlModifier> - <CommandTypeName>RefactorExtractMethodCommand</CommandTypeName> -</HotkeySetting> + + <HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <Key1>M</Key1> + <IsEnabled>true</IsEnabled> + <HasShiftModifier>true</HasShiftModifier> + <HasAltModifier>false</HasAltModifier> + <HasCtrlModifier>true</HasCtrlModifier> + <CommandTypeName>RefactorExtractMethodCommand</CommandTypeName> + </HotkeySetting> + - <?xml version="1.0" encoding="utf-16"?> -<HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <Key1>C</Key1> - <IsEnabled>true</IsEnabled> - <HasShiftModifier>true</HasShiftModifier> - <HasAltModifier>false</HasAltModifier> - <HasCtrlModifier>true</HasCtrlModifier> - <CommandTypeName>RefactorMoveCloserToUsageCommand</CommandTypeName> -</HotkeySetting> + + <HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <Key1>C</Key1> + <IsEnabled>true</IsEnabled> + <HasShiftModifier>true</HasShiftModifier> + <HasAltModifier>false</HasAltModifier> + <HasCtrlModifier>true</HasCtrlModifier> + <CommandTypeName>RefactorMoveCloserToUsageCommand</CommandTypeName> + </HotkeySetting> + - <?xml version="1.0" encoding="utf-16"?> -<HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <Key1>R</Key1> - <IsEnabled>true</IsEnabled> - <HasShiftModifier>false</HasShiftModifier> - <HasAltModifier>false</HasAltModifier> - <HasCtrlModifier>true</HasCtrlModifier> - <CommandTypeName>CodeExplorerCommand</CommandTypeName> -</HotkeySetting> + + <HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <Key1>R</Key1> + <IsEnabled>true</IsEnabled> + <HasShiftModifier>false</HasShiftModifier> + <HasAltModifier>false</HasAltModifier> + <HasCtrlModifier>true</HasCtrlModifier> + <CommandTypeName>CodeExplorerCommand</CommandTypeName> + </HotkeySetting> + - <?xml version="1.0" encoding="utf-16"?> -<HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <Key1>E</Key1> - <IsEnabled>true</IsEnabled> - <HasShiftModifier>true</HasShiftModifier> - <HasAltModifier>false</HasAltModifier> - <HasCtrlModifier>true</HasCtrlModifier> - <CommandTypeName>ExportAllCommand</CommandTypeName> -</HotkeySetting> + + <HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <Key1>E</Key1> + <IsEnabled>true</IsEnabled> + <HasShiftModifier>true</HasShiftModifier> + <HasAltModifier>false</HasAltModifier> + <HasCtrlModifier>true</HasCtrlModifier> + <CommandTypeName>ExportAllCommand</CommandTypeName> + </HotkeySetting> + - <?xml version="1.0" encoding="utf-16"?> -<HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <Key1>T</Key1> - <IsEnabled>true</IsEnabled> - <HasShiftModifier>false</HasShiftModifier> - <HasAltModifier>false</HasAltModifier> - <HasCtrlModifier>true</HasCtrlModifier> - <CommandTypeName>FindSymbolCommand</CommandTypeName> -</HotkeySetting> + + <HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <Key1>T</Key1> + <IsEnabled>true</IsEnabled> + <HasShiftModifier>false</HasShiftModifier> + <HasAltModifier>false</HasAltModifier> + <HasCtrlModifier>true</HasCtrlModifier> + <CommandTypeName>FindSymbolCommand</CommandTypeName> + </HotkeySetting> + - <?xml version="1.0" encoding="utf-16"?> -<HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <Key1>M</Key1> - <IsEnabled>true</IsEnabled> - <HasShiftModifier>false</HasShiftModifier> - <HasAltModifier>false</HasAltModifier> - <HasCtrlModifier>true</HasCtrlModifier> - <CommandTypeName>IndentCurrentModuleCommand</CommandTypeName> -</HotkeySetting> + + <HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <Key1>M</Key1> + <IsEnabled>true</IsEnabled> + <HasShiftModifier>false</HasShiftModifier> + <HasAltModifier>false</HasAltModifier> + <HasCtrlModifier>true</HasCtrlModifier> + <CommandTypeName>IndentCurrentModuleCommand</CommandTypeName> + </HotkeySetting> + - <?xml version="1.0" encoding="utf-16"?> -<HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <Key1>P</Key1> - <IsEnabled>true</IsEnabled> - <HasShiftModifier>false</HasShiftModifier> - <HasAltModifier>false</HasAltModifier> - <HasCtrlModifier>true</HasCtrlModifier> - <CommandTypeName>IndentCurrentProcedureCommand</CommandTypeName> -</HotkeySetting> + + <HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <Key1>P</Key1> + <IsEnabled>true</IsEnabled> + <HasShiftModifier>false</HasShiftModifier> + <HasAltModifier>false</HasAltModifier> + <HasCtrlModifier>true</HasCtrlModifier> + <CommandTypeName>IndentCurrentProcedureCommand</CommandTypeName> + </HotkeySetting> + - <?xml version="1.0" encoding="utf-16"?> -<HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <Key1>I</Key1> - <IsEnabled>true</IsEnabled> - <HasShiftModifier>true</HasShiftModifier> - <HasAltModifier>false</HasAltModifier> - <HasCtrlModifier>true</HasCtrlModifier> - <CommandTypeName>InspectionResultsCommand</CommandTypeName> -</HotkeySetting> + + <HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <Key1>I</Key1> + <IsEnabled>true</IsEnabled> + <HasShiftModifier>true</HasShiftModifier> + <HasAltModifier>false</HasAltModifier> + <HasCtrlModifier>true</HasCtrlModifier> + <CommandTypeName>InspectionResultsCommand</CommandTypeName> + </HotkeySetting> + - <?xml version="1.0" encoding="utf-16"?> -<HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <Key1>`</Key1> - <IsEnabled>true</IsEnabled> - <HasShiftModifier>false</HasShiftModifier> - <HasAltModifier>false</HasAltModifier> - <HasCtrlModifier>true</HasCtrlModifier> - <CommandTypeName>ReparseCommand</CommandTypeName> -</HotkeySetting> + + <HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <Key1>`</Key1> + <IsEnabled>true</IsEnabled> + <HasShiftModifier>false</HasShiftModifier> + <HasAltModifier>false</HasAltModifier> + <HasCtrlModifier>true</HasCtrlModifier> + <CommandTypeName>ReparseCommand</CommandTypeName> + </HotkeySetting> + - <?xml version="1.0" encoding="utf-16"?> -<HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <Key1>T</Key1> - <IsEnabled>true</IsEnabled> - <HasShiftModifier>true</HasShiftModifier> - <HasAltModifier>false</HasAltModifier> - <HasCtrlModifier>true</HasCtrlModifier> - <CommandTypeName>TestExplorerCommand</CommandTypeName> -</HotkeySetting> + + <HotkeySetting xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <Key1>T</Key1> + <IsEnabled>true</IsEnabled> + <HasShiftModifier>true</HasShiftModifier> + <HasAltModifier>false</HasAltModifier> + <HasCtrlModifier>true</HasCtrlModifier> + <CommandTypeName>TestExplorerCommand</CommandTypeName> + </HotkeySetting> + - <?xml version="1.0" encoding="utf-16"?> -<ToDoMarker xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema" Text="TODO" /> + + <ToDoMarker xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema" Text="TODO" /> + - <?xml version="1.0" encoding="utf-16"?> -<ToDoMarker xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema" Text="NOTE" /> + + <ToDoMarker xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema" Text="NOTE" /> + - <?xml version="1.0" encoding="utf-16"?> -<ToDoMarker xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema" Text="BUG" /> + + <ToDoMarker xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema" Text="BUG" /> + - <?xml version="1.0" encoding="utf-16"?> -<WindowSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <CodeExplorerVisibleOnStartup>false</CodeExplorerVisibleOnStartup> - <CodeInspectionsVisibleOnStartup>false</CodeInspectionsVisibleOnStartup> - <TestExplorerVisibleOnStartup>false</TestExplorerVisibleOnStartup> - <TodoExplorerVisibleOnStartup>false</TodoExplorerVisibleOnStartup> - <CodeExplorer_SortByName>true</CodeExplorer_SortByName> - <CodeExplorer_SortByCodeOrder>false</CodeExplorer_SortByCodeOrder> - <CodeExplorer_GroupByType>false</CodeExplorer_GroupByType> -</WindowSettings> + + <WindowSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <CodeExplorerVisibleOnStartup>false</CodeExplorerVisibleOnStartup> + <CodeInspectionsVisibleOnStartup>false</CodeInspectionsVisibleOnStartup> + <TestExplorerVisibleOnStartup>false</TestExplorerVisibleOnStartup> + <TodoExplorerVisibleOnStartup>false</TodoExplorerVisibleOnStartup> + <CodeExplorer_SortByName>true</CodeExplorer_SortByName> + <CodeExplorer_SortByCodeOrder>false</CodeExplorer_SortByCodeOrder> + <CodeExplorer_GroupByType>false</CodeExplorer_GroupByType> + </WindowSettings> + - <?xml version="1.0" encoding="utf-16"?> -<UnitTestSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <BindingMode>LateBinding</BindingMode> - <AssertMode>StrictAssert</AssertMode> - <ModuleInit>true</ModuleInit> - <MethodInit>true</MethodInit> - <DefaultTestStubInNewModule>false</DefaultTestStubInNewModule> -</UnitTestSettings> + + <UnitTestSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <BindingMode>LateBinding</BindingMode> + <AssertMode>StrictAssert</AssertMode> + <ModuleInit>true</ModuleInit> + <MethodInit>true</MethodInit> + <DefaultTestStubInNewModule>false</DefaultTestStubInNewModule> + </UnitTestSettings> + - <?xml version="1.0" encoding="utf-16"?> -<GeneralSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> - <Language Code="en-US" /> - <CanShowSplash>true</CanShowSplash> - <CanCheckVersion>true</CanCheckVersion> - <CompileBeforeParse>true</CompileBeforeParse> - <IsSmartIndenterPrompted>false</IsSmartIndenterPrompted> - <IsAutoSaveEnabled>false</IsAutoSaveEnabled> - <AutoSavePeriod>10</AutoSavePeriod> - <UserEditedLogLevel>false</UserEditedLogLevel> - <MinimumLogLevel>0</MinimumLogLevel> - <EnableExperimentalFeatures /> -</GeneralSettings> + + <GeneralSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema"> + <Language Code="en-US" /> + <CanShowSplash>true</CanShowSplash> + <CanCheckVersion>true</CanCheckVersion> + <CompileBeforeParse>true</CompileBeforeParse> + <IsSmartIndenterPrompted>false</IsSmartIndenterPrompted> + <IsAutoSaveEnabled>false</IsAutoSaveEnabled> + <AutoSavePeriod>10</AutoSavePeriod> + <UserEditedLogLevel>false</UserEditedLogLevel> + <MinimumLogLevel>0</MinimumLogLevel> + <EnableExperimentalFeatures /> + </GeneralSettings> + - <?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="MaintainabilityAndReadabilityIssues" /> - <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="MissingAttributeInspection" Severity="Warning" InspectionType="RubberduckOpportunities" /> - <CodeInspection Name="FunctionReturnValueNotUsedInspection" Severity="Warning" InspectionType="CodeQualityIssues" /> - <CodeInspection Name="IllegalAnnotationInspection" Severity="Error" InspectionType="RubberduckOpportunities" /> - <CodeInspection Name="RedundantByRefModifierInspection" Severity="DoNotShow" InspectionType="CodeQualityIssues" /> - <CodeInspection Name="MissingAnnotationArgumentInspection" Severity="Error" InspectionType="CodeQualityIssues" /> - <CodeInspection Name="ModuleScopeDimKeywordInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" /> - <CodeInspection Name="MultilineParameterInspection" Severity="Suggestion" InspectionType="MaintainabilityAndReadabilityIssues" /> - <CodeInspection Name="MultipleDeclarationsInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> - <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="MaintainabilityAndReadabilityIssues" /> - <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="MaintainabilityAndReadabilityIssues" /> - <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="MaintainabilityAndReadabilityIssues" /> - <CodeInspection Name="EmptyCaseBlockInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> - <CodeInspection Name="EmptyDoWhileBlockInspection" Severity="Suggestion" InspectionType="MaintainabilityAndReadabilityIssues" /> - <CodeInspection Name="EmptyElseBlockInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> - <CodeInspection Name="EmptyForEachBlockInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> - <CodeInspection Name="EmptyForLoopBlockInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> - <CodeInspection Name="EmptyIfBlockInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> - <CodeInspection Name="EmptyWhileWendBlockInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> - <CodeInspection Name="EncapsulatePublicFieldInspection" Severity="Suggestion" InspectionType="MaintainabilityAndReadabilityIssues" /> - <CodeInspection Name="HostSpecificExpressionInspection" Severity="Warning" InspectionType="LanguageOpportunities" /> - <CodeInspection Name="HungarianNotationInspection" Severity="Suggestion" InspectionType="MaintainabilityAndReadabilityIssues" /> - <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="MaintainabilityAndReadabilityIssues" /> - <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="MaintainabilityAndReadabilityIssues" /> - <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="MaintainabilityAndReadabilityIssues" /> - <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="MaintainabilityAndReadabilityIssues" /> - <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" /> - </CodeInspections> - <WhitelistedIdentifiers /> - <RunInspectionsOnSuccessfulParse>true</RunInspectionsOnSuccessfulParse> -</CodeInspectionSettings> + <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="MaintainabilityAndReadabilityIssues" /> + <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="MissingAttributeInspection" Severity="Warning" InspectionType="RubberduckOpportunities" /> + <CodeInspection Name="FunctionReturnValueNotUsedInspection" Severity="Warning" InspectionType="CodeQualityIssues" /> + <CodeInspection Name="IllegalAnnotationInspection" Severity="Error" InspectionType="RubberduckOpportunities" /> + <CodeInspection Name="RedundantByRefModifierInspection" Severity="DoNotShow" InspectionType="CodeQualityIssues" /> + <CodeInspection Name="MissingAnnotationArgumentInspection" Severity="Error" InspectionType="CodeQualityIssues" /> + <CodeInspection Name="ModuleScopeDimKeywordInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" /> + <CodeInspection Name="MultilineParameterInspection" Severity="Suggestion" InspectionType="MaintainabilityAndReadabilityIssues" /> + <CodeInspection Name="MultipleDeclarationsInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> + <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="MaintainabilityAndReadabilityIssues" /> + <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="MaintainabilityAndReadabilityIssues" /> + <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="MaintainabilityAndReadabilityIssues" /> + <CodeInspection Name="EmptyCaseBlockInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> + <CodeInspection Name="EmptyDoWhileBlockInspection" Severity="Suggestion" InspectionType="MaintainabilityAndReadabilityIssues" /> + <CodeInspection Name="EmptyElseBlockInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> + <CodeInspection Name="EmptyForEachBlockInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> + <CodeInspection Name="EmptyForLoopBlockInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> + <CodeInspection Name="EmptyIfBlockInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> + <CodeInspection Name="EmptyWhileWendBlockInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /> + <CodeInspection Name="EncapsulatePublicFieldInspection" Severity="Suggestion" InspectionType="MaintainabilityAndReadabilityIssues" /> + <CodeInspection Name="HostSpecificExpressionInspection" Severity="Warning" InspectionType="LanguageOpportunities" /> + <CodeInspection Name="HungarianNotationInspection" Severity="Suggestion" InspectionType="MaintainabilityAndReadabilityIssues" /> + <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="MaintainabilityAndReadabilityIssues" /> + <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="MaintainabilityAndReadabilityIssues" /> + <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="MaintainabilityAndReadabilityIssues" /> + <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="MaintainabilityAndReadabilityIssues" /> + <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="ExcelUdfNameIsValidCellReferenceInspection" Severity="Warning" InspectionType="CodeQualityIssues" /> + </CodeInspections> + <WhitelistedIdentifiers /> + <RunInspectionsOnSuccessfulParse>true</RunInspectionsOnSuccessfulParse> + </CodeInspectionSettings> - <?xml version="1.0" encoding="utf-16"?> -<AutoCompleteSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema" IsEnabled="false"> - <SmartConcat> - <IsEnabled>false</IsEnabled> - <ConcatVbNewLineModifier>None</ConcatVbNewLineModifier> - </SmartConcat> - <SelfClosingPairs IsEnabled="false" /> - <BlockCompletion IsEnabled="false" CompleteOnEnter="false" CompleteOnTab="false" /> -</AutoCompleteSettings> + + <AutoCompleteSettings xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance" xmlns:xsd="http://www.w3.org/2001/XMLSchema" IsEnabled="false"> + <SmartConcat> + <IsEnabled>false</IsEnabled> + <ConcatVbNewLineModifier>None</ConcatVbNewLineModifier> + </SmartConcat> + <SelfClosingPairs IsEnabled="false" /> + <BlockCompletion IsEnabled="false" CompleteOnEnter="false" CompleteOnTab="false" /> + </AutoCompleteSettings> + \ No newline at end of file diff --git a/Rubberduck.Core/Rubberduck.Core.csproj b/Rubberduck.Core/Rubberduck.Core.csproj index aa0e0bf1a2..987baa2cbf 100644 --- a/Rubberduck.Core/Rubberduck.Core.csproj +++ b/Rubberduck.Core/Rubberduck.Core.csproj @@ -108,27 +108,30 @@ Code %(Filename) - + + + Resources.resx true true - - Resources.Designer.cs - ResXFileCodeGenerator - - True True Settings.settings True + + SettingsSingleFileGenerator Settings.Designer.cs + + Resources.Designer.cs + ResXFileCodeGenerator + diff --git a/Rubberduck.Core/app.config b/Rubberduck.Core/app.config index 11c717c6c1..0df00ce776 100644 --- a/Rubberduck.Core/app.config +++ b/Rubberduck.Core/app.config @@ -386,6 +386,8 @@ Severity="Warning" InspectionType="CodeQualityIssues" /> + true From 3643c7ec4cd22a99df506c56c553258fc1b4b6f4 Mon Sep 17 00:00:00 2001 From: comintern Date: Fri, 16 Nov 2018 18:58:14 -0600 Subject: [PATCH 3/3] Roll back change forcing resx designers back into sync --- .../Rubberduck.Resources.csproj | 182 ------------------ 1 file changed, 182 deletions(-) diff --git a/Rubberduck.Resources/Rubberduck.Resources.csproj b/Rubberduck.Resources/Rubberduck.Resources.csproj index ee5d27fff6..1881eb1be9 100644 --- a/Rubberduck.Resources/Rubberduck.Resources.csproj +++ b/Rubberduck.Resources/Rubberduck.Resources.csproj @@ -12,186 +12,4 @@ - - - True - True - $([System.String]::Copy('%(Filename)').Replace('.Designer', '')).resx - - - - - - PublicResXFileCodeGenerator - $([System.String]::Copy('%(FileName)')).Designer.cs - - - - - - True - True - AboutUI.resx - - - True - True - CodeExplorerUI.resx - - - True - True - CommandBarIcons.resx - - - True - True - InspectionInfo.resx - - - True - True - InspectionNames.resx - - - True - True - InspectionResults.resx - - - True - True - InspectionsUI.resx - - - True - True - QuickFixes.resx - - - True - True - RubberduckMenus.resx - - - True - True - RegexAssistantUI.resx - - - True - True - RubberduckUI.resx - - - True - True - AutoCompletesPage.resx - - - True - True - SettingsUI.resx - - - True - True - ToDoExplorerPage.resx - - - True - True - UnitTestingPage.resx - - - True - True - ToDoExplorerUI.resx - - - True - True - AssertMessages.resx - - - True - True - TestExplorer.resx - - - - - - PublicResXFileCodeGenerator - AboutUI.Designer.cs - - - PublicResXFileCodeGenerator - CodeExplorerUI.Designer.cs - - - PublicResXFileCodeGenerator - CommandBarIcons.Designer.cs - - - PublicResXFileCodeGenerator - InspectionInfo.Designer.cs - - - PublicResXFileCodeGenerator - InspectionNames.Designer.cs - - - PublicResXFileCodeGenerator - InspectionResults.Designer.cs - - - PublicResXFileCodeGenerator - InspectionsUI.Designer.cs - - - PublicResXFileCodeGenerator - QuickFixes.Designer.cs - - - PublicResXFileCodeGenerator - RubberduckMenus.Designer.cs - - - PublicResXFileCodeGenerator - RegexAssistantUI.Designer.cs - - - PublicResXFileCodeGenerator - RubberduckUI.Designer.cs - - - PublicResXFileCodeGenerator - AutoCompletesPage.Designer.cs - - - PublicResXFileCodeGenerator - SettingsUI.Designer.cs - - - PublicResXFileCodeGenerator - ToDoExplorerPage.Designer.cs - - - PublicResXFileCodeGenerator - UnitTestingPage.Designer.cs - - - PublicResXFileCodeGenerator - ToDoExplorerUI.Designer.cs - - - PublicResXFileCodeGenerator - AssertMessages.Designer.cs - - - PublicResXFileCodeGenerator - TestExplorer.Designer.cs - - \ No newline at end of file