From e5ea99dbeb0ac795d3dab0a82eda8a2d343f8d76 Mon Sep 17 00:00:00 2001 From: Mathieu Guindon Date: Tue, 6 Apr 2021 01:05:38 -0400 Subject: [PATCH 1/9] fixes document subtype resolution --- .../ImplicitSheetReferenceInspectionBase.cs | 4 ++- .../DeclarationCaching/DeclarationFinder.cs | 27 ++++++++++--------- 2 files changed, 18 insertions(+), 13 deletions(-) diff --git a/Rubberduck.CodeAnalysis/Inspections/Abstract/ImplicitSheetReferenceInspectionBase.cs b/Rubberduck.CodeAnalysis/Inspections/Abstract/ImplicitSheetReferenceInspectionBase.cs index 7160af6643..e4fbe04a03 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Abstract/ImplicitSheetReferenceInspectionBase.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Abstract/ImplicitSheetReferenceInspectionBase.cs @@ -26,6 +26,7 @@ protected override IEnumerable ObjectionableDeclarations(Declaratio .Select(className => finder.FindClassModule(className, excel, true)) .OfType(); + return globalModules .SelectMany(moduleClass => moduleClass.Members) .Where(declaration => TargetMemberNames.Contains(declaration.IdentifierName) @@ -35,7 +36,8 @@ protected override IEnumerable ObjectionableDeclarations(Declaratio private static readonly string[] GlobalObjectClassNames = { - "Global", "_Global" + "Global", "_Global", + "Worksheet", "_Worksheet" }; private static readonly string[] TargetMemberNames = diff --git a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs index fe0c5ca5d6..bf28804592 100644 --- a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs +++ b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs @@ -898,9 +898,10 @@ public Declaration FindDefaultInstanceVariableClassReferencedProject(Declaration string memberName, DeclarationType memberType) { var allMatches = MatchName(memberName); + var parentClass = parent as ClassModuleDeclaration; var memberMatches = allMatches .Where(m => m.DeclarationType.HasFlag(memberType) - && parent.Equals(m.ParentDeclaration)) + && (parent.Equals(m.ParentDeclaration) || (parentClass?.Supertypes.Any(t => t.Equals(m.ParentDeclaration)) ?? false))) .ToList(); var accessibleMembers = memberMatches.Where(m => AccessibilityCheck.IsMemberAccessible(callingProject, callingModule, callingParent, m)); var match = accessibleMembers.FirstOrDefault(); @@ -934,21 +935,23 @@ public Declaration FindMemberEnclosingModule(Declaration callingModule, Declarat } // Classes such as Worksheet have properties such as Range that can be access in a user defined class such as Sheet1, // that's why we have to walk the type hierarchy and find these implementations. - foreach (var supertype in ClassModuleDeclaration.GetSupertypes(callingModule)) + if (callingModule is ClassModuleDeclaration callingClass) { - // Only built-in classes such as Worksheet can be considered "real base classes". - // User created interfaces work differently and don't allow accessing accessing implementations. - if (supertype.IsUserDefined) + foreach (var supertype in callingClass.Supertypes) { - continue; - } - var supertypeMatch = FindMemberEnclosingModule(supertype, callingParent, memberName, memberType); - if (supertypeMatch != null) - { - return supertypeMatch; + // Only built-in classes such as Worksheet can be considered "real base classes". + // User created interfaces work differently and don't allow accessing accessing implementations. + if (supertype.IsUserDefined) + { + continue; + } + var supertypeMatch = FindMemberEnclosingModule(supertype, callingParent, memberName, memberType); + if (supertypeMatch != null) + { + return supertypeMatch; + } } } - return null; } From f6f7fd20366ca8927474f034ed873979b319bf5e Mon Sep 17 00:00:00 2001 From: Mathieu Guindon Date: Tue, 6 Apr 2021 01:55:01 -0400 Subject: [PATCH 2/9] declare public variable for document module --- Rubberduck.Parsing/Symbols/VariableDeclaration.cs | 5 +++-- .../DeclarationResolving/DeclarationResolveRunnerBase.cs | 8 ++++++++ 2 files changed, 11 insertions(+), 2 deletions(-) diff --git a/Rubberduck.Parsing/Symbols/VariableDeclaration.cs b/Rubberduck.Parsing/Symbols/VariableDeclaration.cs index 168dc167da..c5a9e50d46 100644 --- a/Rubberduck.Parsing/Symbols/VariableDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/VariableDeclaration.cs @@ -23,7 +23,8 @@ public sealed class VariableDeclaration : Declaration, IInterfaceExposable bool isArray, VBAParser.AsTypeClauseContext asTypeContext, IEnumerable annotations = null, - Attributes attributes = null) + Attributes attributes = null, + bool isUserDefined = true) : base( qualifiedName, parentDeclaration, @@ -39,7 +40,7 @@ public sealed class VariableDeclaration : Declaration, IInterfaceExposable selection, isArray, asTypeContext, - true, + isUserDefined, annotations, attributes) { diff --git a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs index 4c732528c2..d8e1987334 100644 --- a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs +++ b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs @@ -147,6 +147,14 @@ protected void ResolveDeclarations(QualifiedModuleName module, IParseTree tree, var membersAllowingAttributes = _state.GetMembersAllowingAttributes(module); var moduleDeclaration = NewModuleDeclaration(module, tree, annotationsOnWhiteSpaceLines, attributes, projectDeclaration); + if (moduleDeclaration is DocumentModuleDeclaration documentModule) + { + var varAttributes = new Attributes(); + //varAttributes.AddMemberDescriptionAttribute(documentModule.IdentifierName, "An object variable VBA creates automatically to refer to a specific document module."); + var variableDeclaration = new VariableDeclaration(documentModule.QualifiedName, documentModule, documentModule, + documentModule.IdentifierName, null, true, false, Accessibility.Public, null, null, Selection.Empty, false, null, attributes:varAttributes, isUserDefined:false); + _state.AddDeclaration(variableDeclaration); + } _state.AddDeclaration(moduleDeclaration); var controlDeclarations = DeclarationsFromControls(moduleDeclaration); From d8f93d405d578881132f96c985c938458182fd9a Mon Sep 17 00:00:00 2001 From: Mathieu Guindon Date: Wed, 7 Apr 2021 00:08:55 -0400 Subject: [PATCH 3/9] fixed classification for default instance variable, removed fake variable declaration --- .../Binding/Bindings/SimpleNameDefaultBinding.cs | 2 +- .../DeclarationResolving/DeclarationResolveRunnerBase.cs | 8 -------- 2 files changed, 1 insertion(+), 9 deletions(-) diff --git a/Rubberduck.Parsing/Binding/Bindings/SimpleNameDefaultBinding.cs b/Rubberduck.Parsing/Binding/Bindings/SimpleNameDefaultBinding.cs index 557f0d5a8e..990ac27027 100644 --- a/Rubberduck.Parsing/Binding/Bindings/SimpleNameDefaultBinding.cs +++ b/Rubberduck.Parsing/Binding/Bindings/SimpleNameDefaultBinding.cs @@ -187,7 +187,7 @@ private IBoundExpression ResolveEnclosingProjectNamespace() var defaultInstanceVariableClass = _declarationFinder.FindDefaultInstanceVariableClassEnclosingProject(_project, _module, _name); if (defaultInstanceVariableClass != null) { - return new SimpleNameExpression(defaultInstanceVariableClass, ExpressionClassification.Type, _context); + return new SimpleNameExpression(defaultInstanceVariableClass, ExpressionClassification.Variable, _context); } return null; } diff --git a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs index d8e1987334..4c732528c2 100644 --- a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs +++ b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs @@ -147,14 +147,6 @@ protected void ResolveDeclarations(QualifiedModuleName module, IParseTree tree, var membersAllowingAttributes = _state.GetMembersAllowingAttributes(module); var moduleDeclaration = NewModuleDeclaration(module, tree, annotationsOnWhiteSpaceLines, attributes, projectDeclaration); - if (moduleDeclaration is DocumentModuleDeclaration documentModule) - { - var varAttributes = new Attributes(); - //varAttributes.AddMemberDescriptionAttribute(documentModule.IdentifierName, "An object variable VBA creates automatically to refer to a specific document module."); - var variableDeclaration = new VariableDeclaration(documentModule.QualifiedName, documentModule, documentModule, - documentModule.IdentifierName, null, true, false, Accessibility.Public, null, null, Selection.Empty, false, null, attributes:varAttributes, isUserDefined:false); - _state.AddDeclaration(variableDeclaration); - } _state.AddDeclaration(moduleDeclaration); var controlDeclarations = DeclarationsFromControls(moduleDeclaration); From 862ed33a6e7c0307e98a81f0956206164bc9a27b Mon Sep 17 00:00:00 2001 From: Mathieu Guindon Date: Wed, 7 Apr 2021 00:56:57 -0400 Subject: [PATCH 4/9] Account for qualified calls resolving to _SuperClass --- .../ImplicitWorkbookReferenceInspectionBase.cs | 4 +--- .../Concrete/SheetAccessedUsingStringInspection.cs | 10 +++++----- .../VBA/DeclarationCaching/DeclarationFinder.cs | 11 +++++++++++ .../Symbols/SelectedDeclarationProviderTests.cs | 2 +- 4 files changed, 18 insertions(+), 9 deletions(-) diff --git a/Rubberduck.CodeAnalysis/Inspections/Abstract/ImplicitWorkbookReferenceInspectionBase.cs b/Rubberduck.CodeAnalysis/Inspections/Abstract/ImplicitWorkbookReferenceInspectionBase.cs index 3fd009e56b..12390bd35d 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Abstract/ImplicitWorkbookReferenceInspectionBase.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Abstract/ImplicitWorkbookReferenceInspectionBase.cs @@ -24,9 +24,7 @@ internal ImplicitWorkbookReferenceInspectionBase(IDeclarationFinderProvider decl protected override IEnumerable ObjectionableDeclarations(DeclarationFinder finder) { - var excel = finder.Projects - .SingleOrDefault(project => project.IdentifierName == "Excel" && !project.IsUserDefined); - if (excel == null) + if (!finder.TryFindProjectDeclaration("Excel", out var excel)) { return Enumerable.Empty(); } diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs index bb16ba037e..59a3a97468 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs @@ -61,19 +61,19 @@ public SheetAccessedUsingStringInspection(IDeclarationFinderProvider declaration private static readonly string[] InterestingMembers = { - "Worksheets", "Sheets" + "Worksheets", // gets a Sheets object containing Worksheet objects. + "Sheets", // gets a Sheets object containing all sheets (not just Worksheet sheets) in the qualifying workbook. }; private static readonly string[] InterestingClasses = { - "Workbook" + "Workbook", // unqualified member call + "_Workbook", // qualified member call }; protected override IEnumerable ObjectionableDeclarations(DeclarationFinder finder) { - var excel = finder.Projects - .SingleOrDefault(project => project.IdentifierName == "Excel" && !project.IsUserDefined); - if (excel == null) + if (!finder.TryFindProjectDeclaration("Excel", out var excel)) { return Enumerable.Empty(); } diff --git a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs index bf28804592..851cd52eed 100644 --- a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs +++ b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs @@ -357,6 +357,17 @@ public ICollection FindFormEventHandlers() public IEnumerable Classes => _classes.Value; public IEnumerable Projects => _projects.Value; + /// + /// Gets the object for specified referenced project/library. + /// + /// The identifier name of the project declaration to find. + /// The result, if found; null otherwise. + public bool TryFindProjectDeclaration(string name, out Declaration result) + { + result = _projects.Value.SingleOrDefault(project => project.IdentifierName.Equals(name, StringComparison.InvariantCultureIgnoreCase) && !project.IsUserDefined); + return result != null; + } + public IEnumerable UserDeclarations(DeclarationType type) { return _userDeclarationsByType.TryGetValue(type, out var result) diff --git a/RubberduckTests/Symbols/SelectedDeclarationProviderTests.cs b/RubberduckTests/Symbols/SelectedDeclarationProviderTests.cs index 7652a27de5..fd55671ad9 100644 --- a/RubberduckTests/Symbols/SelectedDeclarationProviderTests.cs +++ b/RubberduckTests/Symbols/SelectedDeclarationProviderTests.cs @@ -527,7 +527,7 @@ public void Identify_NamedParameter_Parameter_FromExcel() .AddProjectToVbeBuilder() .Build(); - var (expected, actual) = DeclarationsFromParse(vbe.Object, DeclarationType.Parameter, "Link", "EXCEL.EXE;Excel.Worksheet.Paste"); + var (expected, actual) = DeclarationsFromParse(vbe.Object, DeclarationType.Parameter, "Link", "EXCEL.EXE;Excel._Worksheet.Paste"); Assert.AreEqual(expected, actual); } From 318939bb09c147031c013ef778d6e5797ffa326a Mon Sep 17 00:00:00 2001 From: Mathieu Guindon Date: Wed, 7 Apr 2021 01:57:16 -0400 Subject: [PATCH 5/9] added missing DeclarationType resource key --- Rubberduck.Resources/RubberduckUI.Designer.cs | 9 +++++++++ Rubberduck.Resources/RubberduckUI.resx | 3 +++ 2 files changed, 12 insertions(+) diff --git a/Rubberduck.Resources/RubberduckUI.Designer.cs b/Rubberduck.Resources/RubberduckUI.Designer.cs index 6ac838d2dc..655bb19695 100644 --- a/Rubberduck.Resources/RubberduckUI.Designer.cs +++ b/Rubberduck.Resources/RubberduckUI.Designer.cs @@ -1210,6 +1210,15 @@ public class RubberduckUI { } } + /// + /// Looks up a localized string similar to document. + /// + public static string DeclarationType_Document { + get { + return ResourceManager.GetString("DeclarationType_Document", resourceCulture); + } + } + /// /// Looks up a localized string similar to enum. /// diff --git a/Rubberduck.Resources/RubberduckUI.resx b/Rubberduck.Resources/RubberduckUI.resx index 885d466fa3..6c4ff4ca4e 100644 --- a/Rubberduck.Resources/RubberduckUI.resx +++ b/Rubberduck.Resources/RubberduckUI.resx @@ -1892,4 +1892,7 @@ Do you want to proceed? Remove vertical space between related property members + + document + \ No newline at end of file From c5ad714fd490c89e2c4554e032a6dbf34f00d819 Mon Sep 17 00:00:00 2001 From: Mathieu Guindon Date: Wed, 7 Apr 2021 09:31:23 -0400 Subject: [PATCH 6/9] address a few possible exceptions --- .../Concrete/AssignmentNotUsedInspection.cs | 13 ++++++------- .../VBA/DeclarationCaching/DeclarationFinder.cs | 7 ++++--- 2 files changed, 10 insertions(+), 10 deletions(-) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs index a944cf3f6d..25c11f4492 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs @@ -131,20 +131,19 @@ private static IEnumerable FindUnusedAssignmentNodes(INode node, .Contains(refNode)); var assignmentsPrecedingReference = assignmentExprNodesWithReference.Any() - ? assignmentExprNodes.TakeWhile(n => n != assignmentExprNodesWithReference.Last()) - .Last() - .Nodes(new[] { typeof(AssignmentNode) }) + ? assignmentExprNodes.TakeWhile(n => n != assignmentExprNodesWithReference.LastOrDefault()) + ?.LastOrDefault() + ?.Nodes(new[] { typeof(AssignmentNode) }) : allAssignmentsAndReferences.TakeWhile(n => n != refNode) .OfType(); - if (assignmentsPrecedingReference.Any()) + if (assignmentsPrecedingReference?.Any() ?? false) { - usedAssignments.Add(assignmentsPrecedingReference.Last() as AssignmentNode); + usedAssignments.Add(assignmentsPrecedingReference.LastOrDefault() as AssignmentNode); } } - return allAssignmentsAndReferences.OfType() - .Except(usedAssignments); + return allAssignmentsAndReferences.OfType().Except(usedAssignments); } private static bool IsDescendentOfNeverFlagNode(AssignmentNode assignment) diff --git a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs index 851cd52eed..bb1cc114fd 100644 --- a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs +++ b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs @@ -333,7 +333,7 @@ public IEnumerable FindEventHandlers(Declaration e { var withEventsDeclarations = FindWithEventFields(eventDeclaration); return withEventsDeclarations - .Select(withEventsField => FindHandlersForWithEventsField(withEventsField).Single(handler => + .Select(withEventsField => FindHandlersForWithEventsField(withEventsField).SingleOrDefault(handler => handler.IdentifierName.Equals($"{withEventsField.IdentifierName}_{eventDeclaration.IdentifierName}", StringComparison.InvariantCultureIgnoreCase))); } @@ -362,9 +362,10 @@ public ICollection FindFormEventHandlers() /// /// The identifier name of the project declaration to find. /// The result, if found; null otherwise. - public bool TryFindProjectDeclaration(string name, out Declaration result) + /// True to include user-defined projects in the search; false by default. + public bool TryFindProjectDeclaration(string name, out Declaration result, bool includeUserDefined = false) { - result = _projects.Value.SingleOrDefault(project => project.IdentifierName.Equals(name, StringComparison.InvariantCultureIgnoreCase) && !project.IsUserDefined); + result = _projects.Value.FirstOrDefault(project => project.IdentifierName.Equals(name, StringComparison.InvariantCultureIgnoreCase) && project.IsUserDefined == includeUserDefined); return result != null; } From 49c7444ed6bf33f5c9c3361cb7322afa220d3bba Mon Sep 17 00:00:00 2001 From: bclothier Date: Wed, 7 Apr 2021 09:02:20 -0500 Subject: [PATCH 7/9] Closes #5722 Reverts the change from #5675 --- .../TypeLibs/TypeLibVBEExtensions.cs | 35 ++++++++++--------- 1 file changed, 18 insertions(+), 17 deletions(-) diff --git a/Rubberduck.VBEEditor/ComManagement/TypeLibs/TypeLibVBEExtensions.cs b/Rubberduck.VBEEditor/ComManagement/TypeLibs/TypeLibVBEExtensions.cs index 11f3a4288a..9d29ba9dbc 100644 --- a/Rubberduck.VBEEditor/ComManagement/TypeLibs/TypeLibVBEExtensions.cs +++ b/Rubberduck.VBEEditor/ComManagement/TypeLibs/TypeLibVBEExtensions.cs @@ -89,23 +89,24 @@ public bool CompileProject() { try { - // Prevent a potential access violation by first calling the Placeholder3(). - // Under certain conditions where the VBA project is fully compiled, clicking parse - // as soon as Rubberduck has loaded into VBIDE can cause an access violation when - // accessing CompileProject(). We've tried using ComMessagePumper and - // UiDispatcher.FlushMessageQueue but neither helped in preventing the - // access violation. We at least know that Placeholder3() does not save the unsaved - // change so hopefully there should be no permanent side effects from invoking the - // Placeholder3(). - try - { - _target_IVBEProject.Placeholder3(); - } - catch(Exception ex) - { - Logger.Info(ex, $"Cannot compile the VBA project '{_name}' because there may be a potential access violation."); - return false; - } + // FIXME: Prevent an access violation when calling CompileProject(). A easy way to reproduce + // this AV is to parse an Access project, then do a Compact & Repair, then try to shut down + // Access. There was an attempt to avoid the AV by calling PlaceHolder3 which did seem to prevent + // the AV but somehow alters the VBA project in such way that _sometimes_ the user is shown a message + // that the project has changed and whether the user wants to proceeds. That is a slightly worse fix + // than the AV prevention, so we had to remove the fix. Reference: + // https://github.com/rubberduck-vba/Rubberduck/issues/5722 + // https://github.com/rubberduck-vba/Rubberduck/pull/5675 + + //try + //{ + // _target_IVBEProject.Placeholder3(); + //} + //catch(Exception ex) + //{ + // Logger.Info(ex, $"Cannot compile the VBA project '{_name}' because there may be a potential access violation."); + // return false; + //} _target_IVBEProject.CompileProject(); return true; From 8cdb9ec533e273d925d004168d055a4d791bd34b Mon Sep 17 00:00:00 2001 From: Mathieu Guindon Date: Thu, 8 Apr 2021 10:52:02 -0400 Subject: [PATCH 8/9] Added remarks to xmldoc Explains why the inspection isn't flagging a `ByRef` parameter that is passed as an argument to a procedure that also accepts it `ByRef`; also adds an example for that specific scenario. --- .../Concrete/ParameterCanBeByValInspection.cs | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterCanBeByValInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterCanBeByValInspection.cs index 5e8de860fb..2af67e9394 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterCanBeByValInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterCanBeByValInspection.cs @@ -19,6 +19,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete /// a parameter that is passed by reference (implicitly, or explicitly ByRef) makes it ambiguous from the calling code's standpoint, whether the /// procedure might re-assign these ByRef values and introduce a bug. /// + /// For performance reasons, this inspection will not flag a parameter that is passed as an argument to a procedure that also accepts it ByRef. /// /// /// /// /// + /// + /// + /// + /// + /// internal sealed class ParameterCanBeByValInspection : DeclarationInspectionBase { public ParameterCanBeByValInspection(IDeclarationFinderProvider declarationFinderProvider) From bffa62e1214a4320e2f1ca3506c3d39fd5811259 Mon Sep 17 00:00:00 2001 From: Mathieu Guindon Date: Thu, 8 Apr 2021 10:58:54 -0400 Subject: [PATCH 9/9] fixes the broken xmldoc example ContentUpdater app is unable to parse the example code because the code is outside of the `` tag. --- .../Annotations/Concrete/EntryPointAnnotation.cs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Rubberduck.Parsing/Annotations/Concrete/EntryPointAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/EntryPointAnnotation.cs index 12f563933d..d2dc2aa966 100644 --- a/Rubberduck.Parsing/Annotations/Concrete/EntryPointAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Concrete/EntryPointAnnotation.cs @@ -16,7 +16,6 @@ namespace Rubberduck.Parsing.Annotations.Concrete /// /// /// - /// /// + /// /// public sealed class EntryPointAnnotation : AnnotationBase { @@ -69,4 +69,4 @@ public override IReadOnlyList ProcessAnnotationArguments(IEnumerable