From d865e3d9876e44488b3c94e78368a4cc20b9509c Mon Sep 17 00:00:00 2001 From: Vogel612 Date: Mon, 26 Aug 2019 21:01:12 +0200 Subject: [PATCH 1/4] Redesign Annotation Processing This redesigns annotation processing to no longer rely on the AnnotationTypes enum to identify an annotation, allowing us to separate the scoping of an annotation from it's type. Additionally this explicitly stores metainformation on annotations in Attributes on the specific annotation type. This metainformation is used to automatically register annotations for the code pane parsing process. These changes have far-reaching implications for how annotations are used, most of them addressed in this commit. The parsing of annotations through the VBA API is not correctly dealt with. --- Rubberduck.API/VBA/Parser.cs | 6 +- .../AttributeValueOutOfSyncInspection.cs | 2 +- .../DuplicatedAnnotationInspection.cs | 4 +- .../Concrete/IllegalAnnotationInspection.cs | 2 +- .../MissingAnnotationArgumentInspection.cs | 6 +- .../Concrete/MissingAttributeInspection.cs | 2 +- .../Concrete/ModuleWithoutFolderInspection.cs | 2 +- .../Concrete/ObsoleteMemberUsageInspection.cs | 6 +- .../AdjustAttributeAnnotationQuickFix.cs | 8 +- .../QuickFixes/IgnoreOnceQuickFix.cs | 8 +- .../RemoveDuplicatedAnnotationQuickFix.cs | 2 +- .../CodeExplorerComponentViewModel.cs | 2 +- .../CodeExplorerMemberViewModel.cs | 2 +- .../UI/CodeExplorer/Commands/IndentCommand.cs | 10 +- .../ComCommands/NoIndentAnnotationCommand.cs | 2 +- .../CodeExplorerNodeToIconConverter.cs | 2 +- .../ComCommands/AddTestMethodCommand.cs | 2 +- .../AddTestMethodExpectedErrorCommand.cs | 2 +- .../UI/UnitTesting/TestExplorerViewModel.cs | 5 +- .../Output/StringExtensions.cs | 23 +- .../Root/RubberduckIoCInstaller.cs | 20 ++ .../Annotations/AnnotationBase.cs | 16 +- .../Annotations/AnnotationType.cs | 115 -------- .../AttributeAnnotationProvider.cs | 171 +++++++----- .../Annotations/ExcelHotKeyAnnotation.cs | 23 -- .../FixedAttributeValueAnnotationBase.cs | 40 --- Rubberduck.Parsing/Annotations/IAnnotation.cs | 46 ++- .../Annotations/IAttributeAnnotation.cs | 42 +++ .../IAttributeAnnotationProvider.cs | 4 +- .../DefaultMemberAnnotation.cs | 5 +- .../DescriptionAnnotation.cs | 4 +- .../DescriptionAttributeAnnotationBase.cs | 4 +- .../EnumeratorMemberAnnotation.cs | 4 +- .../Implementations/ExcelHotKeyAnnotation.cs | 24 ++ .../ExposedModuleAnnotation.cs | 4 +- .../FixedAttributeValueAnnotationBase.cs | 36 +++ .../FlexibleAttributeAnnotationBase.cs | 4 +- .../FlexibleAttributeValueAnnotationBase.cs | 22 +- .../{ => Implementations}/FolderAnnotation.cs | 3 +- .../{ => Implementations}/IgnoreAnnotation.cs | 15 +- .../IgnoreModuleAnnotation.cs | 8 +- .../IgnoreTestAnnotation.cs | 3 +- .../InterfaceAnnotation.cs | 3 +- .../MemberAttributeAnnotation.cs | 23 ++ .../ModuleAttributeAnnotation.cs | 7 +- .../ModuleCleanupAnnotation.cs | 3 +- .../ModuleDescriptionAnnotation.cs | 7 +- .../ModuleInitializeAnnotation.cs | 3 +- .../NoIndentAnnotation.cs | 3 +- .../NotRecognizedAnnotation.cs | 4 +- .../ObsoleteAnnotation.cs | 3 +- .../PredeclaredIdAnnotation.cs | 4 +- .../TestCleanupAnnotation.cs | 3 +- .../TestInitializeAnnotation.cs | 3 +- .../TestMethodAnnotation.cs | 5 +- .../TestModuleAnnotation.cs | 4 +- .../VariableDescriptionAnnotation.cs | 4 +- .../Annotations/MemberAttributeAnnotation.cs | 13 - .../Annotations/VBAParserAnnotationFactory.cs | 48 ++-- .../PartialExtensions/IAnnotatedContext.cs | 2 +- .../VBAParserPartialExtensions.cs | 3 +- Rubberduck.Parsing/Rubberduck.Parsing.csproj | 1 + Rubberduck.Parsing/Symbols/Attributes.cs | 2 +- .../Symbols/ModuleDeclaration.cs | 4 +- Rubberduck.Parsing/VBA/AnnotationUpdater.cs | 83 +++--- .../DeclarationCaching/DeclarationFinder.cs | 14 +- .../DeclarationResolveRunnerBase.cs | 4 +- .../DeclarationSymbolsListener.cs | 10 +- Rubberduck.Parsing/VBA/IAnnotationUpdater.cs | 8 +- .../VBA/Parsing/ModuleParser.cs | 6 +- .../BoundExpressionVisitor.cs | 3 +- .../IdentifierReferenceResolver.cs | 2 +- .../VBA/RubberduckParserState.cs | 4 +- .../UnitTesting/TestDiscovery.cs | 14 +- .../UnitTesting/TestEngine.cs | 2 +- .../UnitTesting/TestMethod.cs | 6 +- .../AttributeAnnotationProviderTests.cs | 60 ++-- .../Commands/UnitTestCommandTests.cs | 6 +- RubberduckTests/Grammar/AnnotationTests.cs | 263 +++--------------- RubberduckTests/Grammar/ResolverTests.cs | 17 +- .../AttributeValueOutOfSyncInspectionTests.cs | 2 +- RubberduckTests/Mocks/MockParser.cs | 13 +- .../PostProcessing/AnnotationUpdaterTests.cs | 20 +- .../AddAttributeAnnotationQuickFixTests.cs | 7 +- .../AdjustAttributeAnnotationQuickFixTests.cs | 5 +- ...RemoveDuplicatedAnnotationQuickFixTests.cs | 2 +- 86 files changed, 661 insertions(+), 753 deletions(-) delete mode 100644 Rubberduck.Parsing/Annotations/AnnotationType.cs delete mode 100644 Rubberduck.Parsing/Annotations/ExcelHotKeyAnnotation.cs delete mode 100644 Rubberduck.Parsing/Annotations/FixedAttributeValueAnnotationBase.cs rename Rubberduck.Parsing/Annotations/{ => Implementations}/DefaultMemberAnnotation.cs (78%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/DescriptionAnnotation.cs (73%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/DescriptionAttributeAnnotationBase.cs (68%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/EnumeratorMemberAnnotation.cs (75%) create mode 100644 Rubberduck.Parsing/Annotations/Implementations/ExcelHotKeyAnnotation.cs rename Rubberduck.Parsing/Annotations/{ => Implementations}/ExposedModuleAnnotation.cs (75%) create mode 100644 Rubberduck.Parsing/Annotations/Implementations/FixedAttributeValueAnnotationBase.cs rename Rubberduck.Parsing/Annotations/{ => Implementations}/FlexibleAttributeAnnotationBase.cs (68%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/FlexibleAttributeValueAnnotationBase.cs (53%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/FolderAnnotation.cs (87%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/IgnoreAnnotation.cs (60%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/IgnoreModuleAnnotation.cs (76%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/IgnoreTestAnnotation.cs (82%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/InterfaceAnnotation.cs (84%) create mode 100644 Rubberduck.Parsing/Annotations/Implementations/MemberAttributeAnnotation.cs rename Rubberduck.Parsing/Annotations/{ => Implementations}/ModuleAttributeAnnotation.cs (53%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/ModuleCleanupAnnotation.cs (84%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/ModuleDescriptionAnnotation.cs (52%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/ModuleInitializeAnnotation.cs (84%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/NoIndentAnnotation.cs (82%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/NotRecognizedAnnotation.cs (76%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/ObsoleteAnnotation.cs (85%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/PredeclaredIdAnnotation.cs (74%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/TestCleanupAnnotation.cs (84%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/TestInitializeAnnotation.cs (84%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/TestMethodAnnotation.cs (77%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/TestModuleAnnotation.cs (72%) rename Rubberduck.Parsing/Annotations/{ => Implementations}/VariableDescriptionAnnotation.cs (68%) delete mode 100644 Rubberduck.Parsing/Annotations/MemberAttributeAnnotation.cs diff --git a/Rubberduck.API/VBA/Parser.cs b/Rubberduck.API/VBA/Parser.cs index 9f457a268b..10c3882b0d 100644 --- a/Rubberduck.API/VBA/Parser.cs +++ b/Rubberduck.API/VBA/Parser.cs @@ -25,6 +25,7 @@ using Rubberduck.Root; using Rubberduck.VBEditor.ComManagement.TypeLibs; using Rubberduck.VBEditor.SourceCodeHandling; +using Rubberduck.Parsing.Annotations; namespace Rubberduck.API.VBA { @@ -106,6 +107,8 @@ internal Parser(object vbe) : this() var preprocessorErrorListenerFactory = new PreprocessingParseErrorListenerFactory(); var preprocessorParser = new VBAPreprocessorParser(preprocessorErrorListenerFactory, preprocessorErrorListenerFactory); var preprocessor = new VBAPreprocessor(preprocessorParser, compilationsArgumentsCache); + // FIXME inject annotation types to allow Rubberduck api users to access Annotations from VBA code + var annotationProcessor = new VBAParserAnnotationFactory(new List()); var mainParseErrorListenerFactory = new MainParseErrorListenerFactory(); var mainTokenStreamParser = new VBATokenStreamParser(mainParseErrorListenerFactory, mainParseErrorListenerFactory); var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider(); @@ -139,7 +142,8 @@ internal Parser(object vbe) : this() var moduleParser = new ModuleParser( codePaneSourceCodeHandler, attributesSourceCodeHandler, - stringParser); + stringParser, + annotationProcessor); var parseRunner = new ParseRunner( _state, parserStateManager, diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs index 1ee69d0dd2..a672a6c140 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs @@ -49,7 +49,7 @@ public AttributeValueOutOfSyncInspection(RubberduckParserState state) protected override IEnumerable DoGetInspectionResults() { var declarationsWithAttributeAnnotations = State.DeclarationFinder.AllUserDeclarations - .Where(declaration => declaration.Annotations.Any(annotation => annotation.AnnotationType.HasFlag(AnnotationType.Attribute))); + .Where(declaration => declaration.Annotations.Any(annotation => annotation is IAttributeAnnotation)); var results = new List(); foreach (var declaration in declarationsWithAttributeAnnotations.Where(decl => decl.QualifiedModuleName.ComponentType != ComponentType.Document)) { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs index c9c5a409bf..2899a925d4 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs @@ -46,8 +46,8 @@ protected override IEnumerable DoGetInspectionResults() foreach (var declaration in State.AllUserDeclarations) { var duplicateAnnotations = declaration.Annotations - .GroupBy(annotation => annotation.AnnotationType) - .Where(group => !group.First().AllowMultiple && group.Count() > 1); + .GroupBy(annotation => annotation.GetType()) + .Where(group => !group.First().MetaInformation.AllowMultiple && group.Count() > 1); issues.AddRange(duplicateAnnotations.Select(duplicate => { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs index 33f9f975e8..10ceffb07b 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs @@ -52,7 +52,7 @@ protected override IEnumerable DoGetInspectionResults() var annotations = State.AllAnnotations; var unboundAnnotations = UnboundAnnotations(annotations, userDeclarations, identifierReferences) - .Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.GeneralAnnotation) + .Where(annotation => !annotation.MetaInformation.Target.HasFlag(AnnotationTarget.General) || annotation.AnnotatedLine == null); var attributeAnnotationsInDocuments = AttributeAnnotationsInDocuments(userDeclarations); diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs index 361a55444b..b79b9b0111 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs @@ -48,10 +48,12 @@ public MissingAnnotationArgumentInspection(RubberduckParserState state) protected override IEnumerable DoGetInspectionResults() { + // FIXME don't actually use listeners here, iterate the Annotations instead + // FIXME don't maintain a separate list for annotations that require arguments, instead use AnnotationAttribute to store that information return (from result in Listener.Contexts let context = (VBAParser.AnnotationContext)result.Context - where context.annotationName().GetText() == AnnotationType.Ignore.ToString() - || context.annotationName().GetText() == AnnotationType.Folder.ToString() + where context.annotationName().GetText() == "Ignore" + || context.annotationName().GetText() == "Folder" where context.annotationArgList() == null select new QualifiedContextInspectionResult(this, string.Format(InspectionResults.MissingAnnotationArgumentInspection, diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs index a740fe1aca..3cddf6320d 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs @@ -48,7 +48,7 @@ public MissingAttributeInspection(RubberduckParserState state) protected override IEnumerable DoGetInspectionResults() { var declarationsWithAttributeAnnotations = State.DeclarationFinder.AllUserDeclarations - .Where(declaration => declaration.Annotations.Any(annotation => annotation.AnnotationType.HasFlag(AnnotationType.Attribute))); + .Where(declaration => declaration.Annotations.Any(annotation => annotation is IAttributeAnnotation)); var results = new List(); foreach (var declaration in declarationsWithAttributeAnnotations.Where(decl => decl.QualifiedModuleName.ComponentType != ComponentType.Document && !decl.IsIgnoringInspectionResultFor(AnnotationName))) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs index 28ae3b4c74..70fd5e5cfa 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs @@ -39,7 +39,7 @@ public ModuleWithoutFolderInspection(RubberduckParserState state) protected override IEnumerable DoGetInspectionResults() { var modulesWithoutFolderAnnotation = State.DeclarationFinder.UserDeclarations(Parsing.Symbols.DeclarationType.Module) - .Where(w => w.Annotations.All(a => a.AnnotationType != AnnotationType.Folder)) + .Where(w => !w.Annotations.OfType().Any()) .ToList(); return modulesWithoutFolderAnnotation diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs index 6fb12df777..895a53df30 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs @@ -58,15 +58,13 @@ protected override IEnumerable DoGetInspectionResults() { var declarations = State.AllUserDeclarations .Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Member) && - declaration.Annotations.Any(annotation =>annotation.AnnotationType == AnnotationType.Obsolete)); + declaration.Annotations.OfType().Any()); var issues = new List(); foreach (var declaration in declarations) { - var replacementDocumentation = - ((ObsoleteAnnotation) declaration.Annotations.First(annotation => - annotation.AnnotationType == AnnotationType.Obsolete)).ReplacementDocumentation; + var replacementDocumentation = declaration.Annotations.OfType().First().ReplacementDocumentation; issues.AddRange(declaration.References.Select(reference => new IdentifierReferenceInspectionResult(this, diff --git a/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeAnnotationQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeAnnotationQuickFix.cs index 54d96755b1..abdca1cde4 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeAnnotationQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeAnnotationQuickFix.cs @@ -39,15 +39,15 @@ public override void Fix(IInspectionResult result, IRewriteSession rewriteSessio } else { - var (newAnnotationType, newAnnotationValues) = _attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues); - _annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotationType, newAnnotationValues); + var (newAnnotation, newAnnotationValues) = _attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues); + _annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotation, newAnnotationValues); } } else { var attributeBaseName = AttributeBaseName(attributeName, declaration); - var (newAnnotationType, newAnnotationValues) = _attributeAnnotationProvider.MemberAttributeAnnotation(attributeBaseName, attributeValues); - _annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotationType, newAnnotationValues); + var (newAnnotation, newAnnotationValues) = _attributeAnnotationProvider.MemberAttributeAnnotation(attributeBaseName, attributeValues); + _annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotation, newAnnotationValues); } } diff --git a/Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs index 497a984341..191c5f6d6e 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs @@ -52,17 +52,17 @@ private void FixNonModule(IInspectionResult result, IRewriteSession rewriteSessi .OfType() .FirstOrDefault(); - var annotationType = AnnotationType.Ignore; + var annotationInfo = typeof(IgnoreAnnotation).GetCustomAttributes(false).OfType().Single(); if (existingIgnoreAnnotation != null) { var annotationValues = existingIgnoreAnnotation.InspectionNames.ToList(); annotationValues.Insert(0, result.Inspection.AnnotationName); - _annotationUpdater.UpdateAnnotation(rewriteSession, existingIgnoreAnnotation, annotationType, annotationValues); + _annotationUpdater.UpdateAnnotation(rewriteSession, existingIgnoreAnnotation, annotationInfo, annotationValues); } else { var annotationValues = new List { result.Inspection.AnnotationName }; - _annotationUpdater.AddAnnotation(rewriteSession, new QualifiedContext(module, result.Context), annotationType, annotationValues); + _annotationUpdater.AddAnnotation(rewriteSession, new QualifiedContext(module, result.Context), annotationInfo, annotationValues); } } @@ -73,7 +73,7 @@ private void FixModule(IInspectionResult result, IRewriteSession rewriteSession) .OfType() .FirstOrDefault(); - var annotationType = AnnotationType.IgnoreModule; + var annotationType = typeof(IgnoreModuleAnnotation).GetCustomAttributes(false).OfType().Single(); if (existingIgnoreModuleAnnotation != null) { var annotationValues = existingIgnoreModuleAnnotation.InspectionNames.ToList(); diff --git a/Rubberduck.CodeAnalysis/QuickFixes/RemoveDuplicatedAnnotationQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/RemoveDuplicatedAnnotationQuickFix.cs index 34d0b49810..1b78d7f910 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/RemoveDuplicatedAnnotationQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/RemoveDuplicatedAnnotationQuickFix.cs @@ -20,7 +20,7 @@ public RemoveDuplicatedAnnotationQuickFix(IAnnotationUpdater annotationUpdater) public override void Fix(IInspectionResult result, IRewriteSession rewriteSession) { var duplicateAnnotations = result.Target.Annotations - .Where(annotation => annotation.AnnotationType == result.Properties.AnnotationType) + .Where(annotation => annotation.GetType() == result.Properties.AnnotationType) .OrderBy(annotation => annotation.Context.Start.StartIndex) .Skip(1) .ToList(); diff --git a/Rubberduck.Core/Navigation/CodeExplorer/CodeExplorerComponentViewModel.cs b/Rubberduck.Core/Navigation/CodeExplorer/CodeExplorerComponentViewModel.cs index 96f11d95a1..b00cbf9f2a 100644 --- a/Rubberduck.Core/Navigation/CodeExplorer/CodeExplorerComponentViewModel.cs +++ b/Rubberduck.Core/Navigation/CodeExplorer/CodeExplorerComponentViewModel.cs @@ -52,7 +52,7 @@ public CodeExplorerComponentViewModel(ICodeExplorerNode parent, Declaration decl Declaration.Attributes.HasPredeclaredIdAttribute(out _); public bool IsTestModule => Declaration.DeclarationType == DeclarationType.ProceduralModule - && Declaration.Annotations.Any(annotation => annotation.AnnotationType == AnnotationType.TestModule); + && Declaration.Annotations.Any(annotation => annotation is TestModuleAnnotation); public override void Synchronize(ref List updated) { diff --git a/Rubberduck.Core/Navigation/CodeExplorer/CodeExplorerMemberViewModel.cs b/Rubberduck.Core/Navigation/CodeExplorer/CodeExplorerMemberViewModel.cs index 496384fbde..a105850106 100644 --- a/Rubberduck.Core/Navigation/CodeExplorer/CodeExplorerMemberViewModel.cs +++ b/Rubberduck.Core/Navigation/CodeExplorer/CodeExplorerMemberViewModel.cs @@ -51,7 +51,7 @@ public override string NameWithSignature } public override bool IsObsolete => - Declaration.Annotations.Any(annotation => annotation.AnnotationType == AnnotationType.Obsolete); + Declaration.Annotations.Any(annotation => annotation is ObsoleteAnnotation); public static readonly DeclarationType[] SubMemberTypes = { diff --git a/Rubberduck.Core/UI/CodeExplorer/Commands/IndentCommand.cs b/Rubberduck.Core/UI/CodeExplorer/Commands/IndentCommand.cs index b6774c07ef..b2eea3f967 100644 --- a/Rubberduck.Core/UI/CodeExplorer/Commands/IndentCommand.cs +++ b/Rubberduck.Core/UI/CodeExplorer/Commands/IndentCommand.cs @@ -53,14 +53,14 @@ private bool SpecialEvaluateCanExecute(object parameter) case CodeExplorerProjectViewModel project: return _state.AllUserDeclarations .Any(c => c.DeclarationType.HasFlag(DeclarationType.Module) && - c.Annotations.All(a => a.AnnotationType != AnnotationType.NoIndent) && + !c.Annotations.Any(a => a is NoIndentAnnotation) && c.ProjectId == project.Declaration.ProjectId); case CodeExplorerCustomFolderViewModel folder: return folder.Children.OfType() //TODO - this has the filter applied. .Select(s => s.Declaration) - .Any(d => d.Annotations.All(a => a.AnnotationType != AnnotationType.NoIndent)); + .Any(d => !d.Annotations.Any(a => a is NoIndentAnnotation)); case CodeExplorerComponentViewModel model: - return model.Declaration.Annotations.All(a => a.AnnotationType != AnnotationType.NoIndent); + return !model.Declaration.Annotations.Any(a => a is NoIndentAnnotation); case CodeExplorerMemberViewModel member: return member.QualifiedSelection.HasValue; default: @@ -85,7 +85,7 @@ protected override void OnExecute(object parameter) var componentDeclarations = _state.AllUserDeclarations.Where(c => c.DeclarationType.HasFlag(DeclarationType.Module) && - c.Annotations.All(a => a.AnnotationType != AnnotationType.NoIndent) && + !c.Annotations.Any(a => a is NoIndentAnnotation) && c.ProjectId == declaration.ProjectId); foreach (var componentDeclaration in componentDeclarations) @@ -99,7 +99,7 @@ protected override void OnExecute(object parameter) { var components = folder.Children.OfType() //TODO: this has the filter applied. .Select(s => s.Declaration) - .Where(d => d.Annotations.All(a => a.AnnotationType != AnnotationType.NoIndent)) + .Where(d => !d.Annotations.Any(a => a is NoIndentAnnotation)) .Select(d => _state.ProjectsProvider.Component(d.QualifiedName.QualifiedModuleName)); foreach (var component in components) diff --git a/Rubberduck.Core/UI/Command/ComCommands/NoIndentAnnotationCommand.cs b/Rubberduck.Core/UI/Command/ComCommands/NoIndentAnnotationCommand.cs index 57e5a6df32..e65a1c6193 100644 --- a/Rubberduck.Core/UI/Command/ComCommands/NoIndentAnnotationCommand.cs +++ b/Rubberduck.Core/UI/Command/ComCommands/NoIndentAnnotationCommand.cs @@ -34,7 +34,7 @@ private bool SpecialEvaluateCanExecute(object parameter) return pane != null && !pane.IsWrappingNullReference && target != null - && target.Annotations.All(a => a.AnnotationType != AnnotationType.NoIndent); + && !target.Annotations.Any(a => a is NoIndentAnnotation); } } diff --git a/Rubberduck.Core/UI/Converters/CodeExplorerNodeToIconConverter.cs b/Rubberduck.Core/UI/Converters/CodeExplorerNodeToIconConverter.cs index 5eec8bceed..72d44a78e6 100644 --- a/Rubberduck.Core/UI/Converters/CodeExplorerNodeToIconConverter.cs +++ b/Rubberduck.Core/UI/Converters/CodeExplorerNodeToIconConverter.cs @@ -105,7 +105,7 @@ public override object Convert(object value, Type targetType, object parameter, return value is ICodeExplorerNode node && node.Declaration != null && DeclarationIcons.ContainsKey(node.Declaration.DeclarationType) - ? node.Declaration.Annotations.Any(a => a.AnnotationType == AnnotationType.TestMethod) + ? node.Declaration.Annotations.Any(a => a is TestMethodAnnotation) ? TestMethodIcon : DeclarationIcons[node.Declaration.DeclarationType] : ExceptionIcon; diff --git a/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodCommand.cs b/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodCommand.cs index a6ca09e7da..656ce78251 100644 --- a/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodCommand.cs +++ b/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodCommand.cs @@ -53,7 +53,7 @@ private bool SpecialEvaluateCanExecute(object parameter) var testModules = _state.AllUserDeclarations.Where(d => d.DeclarationType == DeclarationType.ProceduralModule && - d.Annotations.Any(a => a.AnnotationType == AnnotationType.TestModule)); + d.Annotations.Any(a => a is TestModuleAnnotation)); try { diff --git a/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodExpectedErrorCommand.cs b/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodExpectedErrorCommand.cs index 39fa9c0a51..fd6b99c8d4 100644 --- a/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodExpectedErrorCommand.cs +++ b/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodExpectedErrorCommand.cs @@ -47,7 +47,7 @@ private bool SpecialEvaluateCanExecute(object parameter) } var testModules = _state.AllUserDeclarations.Where(d => d.DeclarationType == DeclarationType.ProceduralModule && - d.Annotations.Any(a => a.AnnotationType == AnnotationType.TestModule)); + d.Annotations.Any(a => a is TestModuleAnnotation)); try { diff --git a/Rubberduck.Core/UI/UnitTesting/TestExplorerViewModel.cs b/Rubberduck.Core/UI/UnitTesting/TestExplorerViewModel.cs index b6c3947e5a..ab143751c9 100644 --- a/Rubberduck.Core/UI/UnitTesting/TestExplorerViewModel.cs +++ b/Rubberduck.Core/UI/UnitTesting/TestExplorerViewModel.cs @@ -10,6 +10,7 @@ using Rubberduck.Common; using Rubberduck.Interaction.Navigation; using Rubberduck.Parsing; +using Rubberduck.Parsing.Annotations; using Rubberduck.Parsing.Rewriter; using Rubberduck.Parsing.VBA; using Rubberduck.Resources; @@ -376,7 +377,7 @@ private void ExecuteIgnoreTestCommand(object parameter) { var rewriteSession = RewritingManager.CheckOutCodePaneSession(); - AnnotationUpdater.AddAnnotation(rewriteSession, _mousedOverTestMethod.Declaration, Parsing.Annotations.AnnotationType.IgnoreTest); + AnnotationUpdater.AddAnnotation(rewriteSession, _mousedOverTestMethod.Declaration, typeof(IgnoreTestAnnotation).GetCustomAttributes(false).OfType().Single()); rewriteSession.TryRewrite(); } @@ -385,7 +386,7 @@ private void ExecuteUnignoreTestCommand(object parameter) { var rewriteSession = RewritingManager.CheckOutCodePaneSession(); var ignoreTestAnnotations = _mousedOverTestMethod.Declaration.Annotations - .Where(iannotations => iannotations.AnnotationType == Parsing.Annotations.AnnotationType.IgnoreTest); + .Where(iannotations => iannotations is IgnoreTestAnnotation); foreach (var ignoreTestAnnotation in ignoreTestAnnotations) { diff --git a/Rubberduck.JunkDrawer/Output/StringExtensions.cs b/Rubberduck.JunkDrawer/Output/StringExtensions.cs index 495f5819f0..b46f26847f 100644 --- a/Rubberduck.JunkDrawer/Output/StringExtensions.cs +++ b/Rubberduck.JunkDrawer/Output/StringExtensions.cs @@ -15,13 +15,32 @@ public static string Capitalize(this string input) tokens[0] = CultureInfo.CurrentUICulture.TextInfo.ToTitleCase(tokens[0]); return string.Join(" ", tokens); } + public static string CapitalizeFirstLetter(this string input) - { + { if (input.Length == 0) { return string.Empty; } return input.Capitalize().Substring(0, 1) + input.Substring(1); - } + } + + public static string UnQuote(this string input) + { + if (input[0] == '"' && input[input.Length - 1] == '"') + { + return input.Substring(1, input.Length - 2); + } + return input; + } + + public static string EnQuote(this string input) + { + if (input[0] == '"' && input[input.Length - 1] == '"') + { + return input; + } + return $"\"{input}\""; + } } } diff --git a/Rubberduck.Main/Root/RubberduckIoCInstaller.cs b/Rubberduck.Main/Root/RubberduckIoCInstaller.cs index a03dd06981..2574059068 100644 --- a/Rubberduck.Main/Root/RubberduckIoCInstaller.cs +++ b/Rubberduck.Main/Root/RubberduckIoCInstaller.cs @@ -56,6 +56,7 @@ using Rubberduck.VBEditor.SafeComWrappers.Abstract; using Rubberduck.VBEditor.SourceCodeHandling; using Rubberduck.VBEditor.VbeRuntime; +using Rubberduck.Parsing.Annotations; namespace Rubberduck.Root { @@ -851,6 +852,7 @@ private void OverridePropertyInjection(IWindsorContainer container) private void RegisterParsingEngine(IWindsorContainer container) { RegisterCustomDeclarationLoadersToParser(container); + RegisterAnnotationProcessing(container); container.Register(Component.For() .ImplementedBy() @@ -945,6 +947,24 @@ private void RegisterParsingEngine(IWindsorContainer container) .LifestyleSingleton()); } + private void RegisterAnnotationProcessing(IWindsorContainer container) + { + var annotations = new List(); + foreach (Assembly referenced in AssembliesToRegister()) + { + annotations.AddRange(referenced.ExportedTypes + .Where(candidate => candidate.IsBasedOn(typeof(IAnnotation)) && !candidate.IsAbstract)); + } + container.Register(Component.For() + .ImplementedBy() + .DependsOn(Dependency.OnValue>(annotations)) + .LifestyleSingleton()); + container.Register(Component.For() + .ImplementedBy() + .DependsOn(Dependency.OnValue>(annotations.Where(annotation => annotation.IsBasedOn(typeof(IAttributeAnnotation))))) + .LifestyleSingleton()); + } + private void RegisterTypeLibApi(IWindsorContainer container) { container.Register(Component.For() diff --git a/Rubberduck.Parsing/Annotations/AnnotationBase.cs b/Rubberduck.Parsing/Annotations/AnnotationBase.cs index a89610976b..6f53013f43 100644 --- a/Rubberduck.Parsing/Annotations/AnnotationBase.cs +++ b/Rubberduck.Parsing/Annotations/AnnotationBase.cs @@ -1,4 +1,5 @@ using System; +using System.Linq; using Rubberduck.Parsing.Grammar; using Rubberduck.VBEditor; @@ -10,24 +11,23 @@ public abstract class AnnotationBase : IAnnotation private readonly Lazy _annotatedLine; - protected AnnotationBase(AnnotationType annotationType, QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context) + protected AnnotationBase(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context) { - AnnotationType = annotationType; QualifiedSelection = qualifiedSelection; Context = context; _annotatedLine = new Lazy(GetAnnotatedLine); + MetaInformation = GetType().GetCustomAttributes(false).OfType().Single(); } - - public AnnotationType AnnotationType { get; } + public QualifiedSelection QualifiedSelection { get; } public VBAParser.AnnotationContext Context { get; } + // sigh... we kinda want to seal this, but can't because it's not inherited from a class... + public AnnotationAttribute MetaInformation { get; } + public string AnnotationType => MetaInformation.Name; public int? AnnotatedLine => _annotatedLine.Value; - public virtual bool AllowMultiple { get; } = false; - - public override string ToString() => $"Annotation Type: {AnnotationType}"; - + public override string ToString() => $"Annotation Type: {GetType()}"; private int? GetAnnotatedLine() { diff --git a/Rubberduck.Parsing/Annotations/AnnotationType.cs b/Rubberduck.Parsing/Annotations/AnnotationType.cs deleted file mode 100644 index f7cecf4df7..0000000000 --- a/Rubberduck.Parsing/Annotations/AnnotationType.cs +++ /dev/null @@ -1,115 +0,0 @@ -using System; -using System.Collections.Generic; - -namespace Rubberduck.Parsing.Annotations -{ - /// - /// Member names are - /// - [Flags] - public enum AnnotationType - { - /// - /// A type for all not recognized annotations. - /// - NotRecognized = 0, - - /// - /// A flag indicating that the annotation type is valid for modules. - /// - ModuleAnnotation = 1 << 1, - - /// - /// A flag indicating that the annotation type is valid for members (method). - /// - MemberAnnotation = 1 << 2, - - /// - /// A flag indicating that the annotation type is valid for variables or constants. - /// - VariableAnnotation = 1 << 3, - - /// - /// A flag indicating that the annotation type is valid for identifier references. - /// - IdentifierAnnotation = 1 << 4, - - /// - /// A flag indicating that the annotation type is valid on everything but modules. - /// - GeneralAnnotation = 1 << 5 | MemberAnnotation | VariableAnnotation | IdentifierAnnotation, - - /// - /// A flag indicating that the annotation type is driving an attribute. - /// - Attribute = 1 << 6, - - TestModule = 1 << 8 | ModuleAnnotation, - ModuleInitialize = 1 << 9 | MemberAnnotation, - ModuleCleanup = 1 << 10 | MemberAnnotation, - TestMethod = 1 << 11 | MemberAnnotation, - TestInitialize = 1 << 12 | MemberAnnotation, - TestCleanup = 1 << 13 | MemberAnnotation, - IgnoreTest = 1 << 14 | MemberAnnotation, - Ignore = 1 << 15 | GeneralAnnotation, - IgnoreModule = 1 << 16 | ModuleAnnotation, - Folder = 1 << 17 | ModuleAnnotation, - NoIndent = 1 << 18 | ModuleAnnotation, - Interface = 1 << 19 | ModuleAnnotation, - [FlexibleAttributeValueAnnotation("VB_Description", 1)] - Description = 1 << 13 | Attribute | MemberAnnotation, - [FixedAttributeValueAnnotation("VB_UserMemId", "0")] - DefaultMember = 1 << 14 | Attribute | MemberAnnotation, - [FixedAttributeValueAnnotation("VB_UserMemId", "-4")] - Enumerator = 1 << 15 | Attribute | MemberAnnotation, - [FixedAttributeValueAnnotation("VB_PredeclaredId", "True")] - PredeclaredId = 1 << 16 | Attribute | ModuleAnnotation, - [FixedAttributeValueAnnotation("VB_Exposed", "True")] - Exposed = 1 << 17 | Attribute | ModuleAnnotation, - Obsolete = 1 << 18 | MemberAnnotation | VariableAnnotation, - [FlexibleAttributeValueAnnotation("VB_Description", 1)] - ModuleDescription = 1 << 19 | Attribute | ModuleAnnotation, - ModuleAttribute = 1 << 20 | Attribute | ModuleAnnotation, - MemberAttribute = 1 << 21 | Attribute | MemberAnnotation | VariableAnnotation, - [FlexibleAttributeValueAnnotation("VB_VarDescription", 1)] - VariableDescription = 1 << 13 | Attribute | VariableAnnotation, - [FlexibleAttributeValueAnnotation("VB_ProcData.VB_Invoke_Func", 1)] - ExcelHotKey = 1 << 16 | Attribute | MemberAnnotation - } - - [AttributeUsage(AttributeTargets.Field)] - public class FixedAttributeValueAnnotationAttribute : Attribute - { - /// - /// Enum value is associated with a VB_Attribute with a fixed value. - /// - /// The name of the associated attribute. - /// If specified, constrains the association to a specific value. - public FixedAttributeValueAnnotationAttribute(string name, params string[] values) - { - AttributeName = name; - AttributeValues = values; - } - - public string AttributeName { get; } - public IReadOnlyList AttributeValues { get; } - } - - [AttributeUsage(AttributeTargets.Field)] - public class FlexibleAttributeValueAnnotationAttribute : Attribute - { - /// - /// Enum value is associated with a VB_Attribute with a fixed number of values taken from the annotation values. - /// - /// The name of the associated attribute. - /// Size of the attribute value list the attribute takes. - public FlexibleAttributeValueAnnotationAttribute(string name, int numberOfParameters) - { - AttributeName = name; - NumberOfParameters = numberOfParameters; - } - - public string AttributeName { get; } - public int NumberOfParameters { get; } - } -} diff --git a/Rubberduck.Parsing/Annotations/AttributeAnnotationProvider.cs b/Rubberduck.Parsing/Annotations/AttributeAnnotationProvider.cs index e33640418b..672b99f566 100644 --- a/Rubberduck.Parsing/Annotations/AttributeAnnotationProvider.cs +++ b/Rubberduck.Parsing/Annotations/AttributeAnnotationProvider.cs @@ -1,109 +1,130 @@ using System; using System.Collections.Generic; using System.Linq; +using System.Reflection; namespace Rubberduck.Parsing.Annotations { public class AttributeAnnotationProvider : IAttributeAnnotationProvider { - public (AnnotationType annotationType, IReadOnlyList values) ModuleAttributeAnnotation( - string attributeName, - IReadOnlyList attributeValues) - { - var moduleAnnotations = ModuleAnnotations(); - return AttributeAnnotation( - moduleAnnotations, - attributeName, - attributeValues, - AnnotationType.ModuleAttribute); - } + // I want to const this, but can't + private readonly AnnotationTarget [] distinctTargets = new AnnotationTarget[] { AnnotationTarget.Identifier, AnnotationTarget.Member, AnnotationTarget.Module, AnnotationTarget.Variable }; + private readonly Dictionary> annotationInfoByTarget + = new Dictionary>(); - private (AnnotationType annotationType, IReadOnlyList values) AttributeAnnotation( - IReadOnlyList annotationTypes, - string attributeName, - IReadOnlyList attributeValues, - AnnotationType fallbackFlexibleAttributeAnnotationType) + // FIXME make sure only AttributeAnnotations are injected here + public AttributeAnnotationProvider(IEnumerable attributeAnnotationTypes) { - var fixedValueAttributeAnnotation = FirstMatchingFixedAttributeValueAnnotation(annotationTypes, attributeName, attributeValues); - if (fixedValueAttributeAnnotation != default) + // set up empty lists to put information into + foreach (var validTarget in distinctTargets) { - return (fixedValueAttributeAnnotation, new List()); + annotationInfoByTarget[validTarget] = new List(); } - - var flexibleValueAttributeAnnotation = FirstMatchingFlexibleAttributeValueAnnotation(annotationTypes, attributeName, attributeValues.Count); - if (flexibleValueAttributeAnnotation != default) + // we're defensively filtering, but theoretically this might be CW's job? + foreach (var annotationType in attributeAnnotationTypes.Where(type => type.GetInterfaces().Contains(typeof(IAttributeAnnotation)))) { - // FIXME special cased bodge for ExcelHotKeyAnnotation to deal with the value transformation: - if (flexibleValueAttributeAnnotation == AnnotationType.ExcelHotKey) + // Extract the static information about the annotation type from it's AnnotationAttribute + var staticInfo = annotationType.GetCustomAttributes(false) + .OfType() + .Single(); + foreach (var validTarget in distinctTargets) { - return (flexibleValueAttributeAnnotation, attributeValues.Select(keySpec => '"' + keySpec.Substring(1, 1) + '"').ToList()); + if (staticInfo.Target.HasFlag(validTarget)) + { + annotationInfoByTarget[validTarget].Add(annotationType); + } } - return (flexibleValueAttributeAnnotation, attributeValues); } - - var annotationValues = WithNewValuePrepended(attributeValues, attributeName); - return (fallbackFlexibleAttributeAnnotationType, annotationValues); - } - - private static IReadOnlyList ModuleAnnotations() - { - var type = typeof(AnnotationType); - return Enum.GetValues(type) - .Cast() - .Where(annotationType => annotationType.HasFlag(AnnotationType.ModuleAnnotation)) - .ToList(); } - private static AnnotationType FirstMatchingFixedAttributeValueAnnotation( - IEnumerable annotationTypes, - string attributeName, - IEnumerable attributeValues) + public (AnnotationAttribute annotationInfo, IReadOnlyList values) MemberAttributeAnnotation(string attributeBaseName, IReadOnlyList attributeValues) { - var type = typeof(AnnotationType); - return annotationTypes.FirstOrDefault(annotationType => type.GetField(Enum.GetName(type, annotationType)) - .GetCustomAttributes(false) - .OfType() - .Any(attribute => attribute.AttributeName.Equals(attributeName, StringComparison.OrdinalIgnoreCase) - && attribute.AttributeValues.SequenceEqual(attributeValues))); + // quasi-const + var fallbackType = typeof(MemberAttributeAnnotation); + // go through all non-module annotations (contrary to only member annotations) + var memberAnnotationTypes = annotationInfoByTarget[AnnotationTarget.Member] + .Concat(annotationInfoByTarget[AnnotationTarget.Variable]) + .Concat(annotationInfoByTarget[AnnotationTarget.Identifier]); + foreach (var type in memberAnnotationTypes) + { + if (MatchesAttributeNameAndValue(type, attributeBaseName, attributeValues, out var codePassAnnotationValues)) + { + return (GetAttribute(type), codePassAnnotationValues); + } + } + return BuildFallback(attributeBaseName, attributeValues, fallbackType); } - private static AnnotationType FirstMatchingFlexibleAttributeValueAnnotation( - IEnumerable annotationTypes, - string attributeName, - int valueCount) + public (AnnotationAttribute annotationInfo, IReadOnlyList values) ModuleAttributeAnnotation(string attributeName, IReadOnlyList attributeValues) { - var type = typeof(AnnotationType); - return annotationTypes.FirstOrDefault(annotationType => type.GetField(Enum.GetName(type, annotationType)) - .GetCustomAttributes(false) - .OfType() - .Any(attribute => attribute.AttributeName.Equals(attributeName, StringComparison.OrdinalIgnoreCase) - && attribute.NumberOfParameters == valueCount)); + // quasi-const + var fallbackType = typeof(ModuleAttributeAnnotation); + var moduleAnnotationTypes = annotationInfoByTarget[AnnotationTarget.Module]; + foreach (var type in moduleAnnotationTypes) + { + if (MatchesAttributeNameAndValue(type, attributeName, attributeValues, out var codePassAnnotationValues)) + { + return (GetAttribute(type), codePassAnnotationValues); + } + } + return BuildFallback(attributeName, attributeValues, fallbackType); } - private IReadOnlyList WithNewValuePrepended(IReadOnlyList oldList, string newValue) + private bool MatchesAttributeNameAndValue(Type type, string attributeName, IReadOnlyList attributeValues, out IReadOnlyList codePassAnnotationValues) { - var newList = oldList.ToList(); - newList.Insert(0, newValue); - return newList; + codePassAnnotationValues = attributeValues; + if (typeof(FlexibleAttributeAnnotationBase).IsAssignableFrom(type)) + { + // this is always the fallback case, which must only be accepted if all other options are exhausted. + return false; + } + if (typeof(FixedAttributeValueAnnotationBase).IsAssignableFrom(type)) + { + var attributeInfo = GetAttribute(type); + if (attributeInfo.AttributeName.Equals(attributeName, StringComparison.OrdinalIgnoreCase) + && attributeInfo.AttributeValues.SequenceEqual(attributeValues)) + { + // there is no way to set a value in the annotation, therefore we discard the attribute values + codePassAnnotationValues = new List(); + return true; + } + } + if (typeof(FlexibleAttributeValueAnnotationBase).IsAssignableFrom(type)) + { + // obtain flexible attribute information + var attributeInfo = GetAttribute(type); + if (attributeInfo.AttributeName.Equals(attributeName, StringComparison.OrdinalIgnoreCase) + && attributeInfo.NumberOfParameters == attributeValues.Count) + { + if (attributeInfo.HasCustomTransformation) + { + try { + // dispatch to custom transformation + codePassAnnotationValues = ((IEnumerable)type.GetMethod("TransformToAnnotationValues", new[] { typeof(IEnumerable) }) + .Invoke(null, new[] { attributeValues })).ToList(); + } + catch (Exception) + { + codePassAnnotationValues = attributeValues; + } + } + return true; + } + } + return false; } - public (AnnotationType annotationType, IReadOnlyList values) MemberAttributeAnnotation(string attributeBaseName, IReadOnlyList attributeValues) + private (AnnotationAttribute annotationInfo, IReadOnlyList values) BuildFallback(string attributeBaseName, IReadOnlyList attributeValues, Type fallbackType) { - var nonModuleAnnotations = NonModuleAnnotations(); - return AttributeAnnotation( - nonModuleAnnotations, - attributeBaseName, - attributeValues, - AnnotationType.MemberAttribute); + var fallbackValues = new[] { attributeBaseName }.Concat(attributeValues).ToList(); + return (GetAttribute(fallbackType), fallbackValues); } - private static IReadOnlyList NonModuleAnnotations() + private static T GetAttribute(Type annotationType) { - var type = typeof(AnnotationType); - return Enum.GetValues(type) - .Cast() - .Where(annotationType => !annotationType.HasFlag(AnnotationType.ModuleAnnotation)) - .ToList(); + return annotationType.GetCustomAttributes(false) + .OfType() + .Single(); } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/ExcelHotKeyAnnotation.cs b/Rubberduck.Parsing/Annotations/ExcelHotKeyAnnotation.cs deleted file mode 100644 index af72c18d9f..0000000000 --- a/Rubberduck.Parsing/Annotations/ExcelHotKeyAnnotation.cs +++ /dev/null @@ -1,23 +0,0 @@ -using System; -using System.Collections.Generic; -using System.Linq; -using Rubberduck.Parsing.Grammar; -using Rubberduck.VBEditor; - -namespace Rubberduck.Parsing.Annotations -{ - public sealed class ExcelHotKeyAnnotation : FlexibleAttributeValueAnnotationBase - { - public ExcelHotKeyAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable annotationParameterValues) : - base(AnnotationType.ExcelHotKey, qualifiedSelection, context, GetHotKeyAttributeValue(annotationParameterValues)) - { } - - private static IEnumerable GetHotKeyAttributeValue(IEnumerable parameters) => - parameters.Take(1).Select(StripStringLiteralQuotes).Select(v => @"""" + v[0] + @"\n14""").ToList(); - - private static string StripStringLiteralQuotes(string value) => - value.StartsWith("\"") && value.EndsWith("\"") && value.Length > 2 - ? value.Substring(1, value.Length - 2) - : value; - } -} diff --git a/Rubberduck.Parsing/Annotations/FixedAttributeValueAnnotationBase.cs b/Rubberduck.Parsing/Annotations/FixedAttributeValueAnnotationBase.cs deleted file mode 100644 index d8fa2f41b4..0000000000 --- a/Rubberduck.Parsing/Annotations/FixedAttributeValueAnnotationBase.cs +++ /dev/null @@ -1,40 +0,0 @@ -using System; -using System.Collections.Generic; -using System.Linq; -using Rubberduck.Parsing.Grammar; -using Rubberduck.VBEditor; - -namespace Rubberduck.Parsing.Annotations -{ - public abstract class FixedAttributeValueAnnotationBase : AnnotationBase, IAttributeAnnotation - { - protected FixedAttributeValueAnnotationBase(AnnotationType annotationType, QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context) - : base(annotationType, qualifiedSelection, context) - { - var fixedAttributeValueInfo = FixedAttributeValueInfo(annotationType); - - Attribute = fixedAttributeValueInfo?.attribute ?? string.Empty; - AttributeValues = fixedAttributeValueInfo?.attributeValues ?? new List(); - } - - public string Attribute { get; } - public IReadOnlyList AttributeValues { get; } - - private static (string attribute, IReadOnlyList attributeValues)? FixedAttributeValueInfo(AnnotationType annotationType) - { - var type = annotationType.GetType(); - var name = Enum.GetName(type, annotationType); - var flexibleAttributeValueAttributes = type.GetField(name).GetCustomAttributes(false) - .OfType().ToList(); - - var attribute = flexibleAttributeValueAttributes.FirstOrDefault(); - - if (attribute == null) - { - return null; - } - - return (attribute.AttributeName, attribute.AttributeValues); - } - } -} \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/IAnnotation.cs b/Rubberduck.Parsing/Annotations/IAnnotation.cs index 94b3c0247a..6274cefba9 100644 --- a/Rubberduck.Parsing/Annotations/IAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/IAnnotation.cs @@ -1,14 +1,56 @@ using Rubberduck.Parsing.Grammar; using Rubberduck.VBEditor; +using System; namespace Rubberduck.Parsing.Annotations { public interface IAnnotation { - AnnotationType AnnotationType { get; } QualifiedSelection QualifiedSelection { get; } - bool AllowMultiple { get; } VBAParser.AnnotationContext Context { get; } int? AnnotatedLine { get; } + AnnotationAttribute MetaInformation { get; } + + string AnnotationType { get; } + } + + [AttributeUsage(AttributeTargets.Class, AllowMultiple = false, Inherited = false)] + public class AnnotationAttribute : Attribute + { + public string Name { get; } + public AnnotationTarget Target { get; } + public bool AllowMultiple { get; } + + public AnnotationAttribute(string name, AnnotationTarget target, bool allowMultiple = false) + { + Name = name; + Target = target; + AllowMultiple = allowMultiple; + } + } + + [Flags] + public enum AnnotationTarget + { + /// + /// Indicates that the annotation is valid for modules. + /// + Module = 1 << 0, + /// + /// Indicates that the annotation is valid for members. + /// + Member = 1 << 1, + /// + /// Indicates that the annotation is valid for variables or constants. + /// + Variable = 1 << 2, + /// + /// Indicates that the annotation is valid for identifier references. + /// + Identifier = 1 << 3, + /// + /// A convenience access indicating that the annotation is valid for Members, Variables and Identifiers. + /// + General = Member | Variable | Identifier, } } diff --git a/Rubberduck.Parsing/Annotations/IAttributeAnnotation.cs b/Rubberduck.Parsing/Annotations/IAttributeAnnotation.cs index 77aa7c5f2f..9e71b0afa7 100644 --- a/Rubberduck.Parsing/Annotations/IAttributeAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/IAttributeAnnotation.cs @@ -1,3 +1,4 @@ +using System; using System.Collections.Generic; namespace Rubberduck.Parsing.Annotations @@ -7,4 +8,45 @@ public interface IAttributeAnnotation : IAnnotation string Attribute { get; } IReadOnlyList AttributeValues { get; } } + // attributes are disjoint to avoid issues around security and multiple attributes + [AttributeUsage(AttributeTargets.Class, AllowMultiple = false, Inherited = false)] + public class FixedAttributeValueAnnotationAttribute : Attribute + { + /// + /// Enum value is associated with a VB_Attribute with a fixed value. + /// + /// The name of the associated attribute. + /// If specified, constrains the association to a specific value. + public FixedAttributeValueAnnotationAttribute(string name, params string[] values) + { + AttributeName = name; + AttributeValues = values; + } + + public string AttributeName { get; } + public IReadOnlyList AttributeValues { get; } + } + + [AttributeUsage(AttributeTargets.Class, AllowMultiple = false, Inherited = false)] + public class FlexibleAttributeValueAnnotationAttribute : Attribute + { + /// + /// Enum value is associated with a VB_Attribute with a fixed number of values taken from the annotation values. + /// + /// The name of the associated attribute. + /// Size of the attribute value list the attribute takes. + /// + /// A function used during parsing to transform the values stored in the exported attribute to those stored in the code pass annotation arguments. + /// + public FlexibleAttributeValueAnnotationAttribute(string name, int numberOfParameters, bool hasCustomTransform = false) + { + AttributeName = name; + NumberOfParameters = numberOfParameters; + HasCustomTransformation = hasCustomTransform; + } + + public string AttributeName { get; } + public int NumberOfParameters { get; } + public bool HasCustomTransformation { get; } + } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/IAttributeAnnotationProvider.cs b/Rubberduck.Parsing/Annotations/IAttributeAnnotationProvider.cs index d04d75e558..bb155c5a46 100644 --- a/Rubberduck.Parsing/Annotations/IAttributeAnnotationProvider.cs +++ b/Rubberduck.Parsing/Annotations/IAttributeAnnotationProvider.cs @@ -4,7 +4,7 @@ namespace Rubberduck.Parsing.Annotations { public interface IAttributeAnnotationProvider { - (AnnotationType annotationType, IReadOnlyList values) ModuleAttributeAnnotation(string attributeName, IReadOnlyList attributeValues); - (AnnotationType annotationType, IReadOnlyList values) MemberAttributeAnnotation(string attributeBaseName, IReadOnlyList attributeValues); + (AnnotationAttribute annotationInfo, IReadOnlyList values) ModuleAttributeAnnotation(string attributeName, IReadOnlyList attributeValues); + (AnnotationAttribute annotationInfo, IReadOnlyList values) MemberAttributeAnnotation(string attributeBaseName, IReadOnlyList attributeValues); } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/DefaultMemberAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/DefaultMemberAnnotation.cs similarity index 78% rename from Rubberduck.Parsing/Annotations/DefaultMemberAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/DefaultMemberAnnotation.cs index f70e078365..9f61332910 100644 --- a/Rubberduck.Parsing/Annotations/DefaultMemberAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/DefaultMemberAnnotation.cs @@ -8,10 +8,13 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for specifying a member's VB_UserMemId attribute value. /// + /// + [Annotation("DefaultMember", AnnotationTarget.Member)] + [FixedAttributeValueAnnotation("VB_UserMemId", "0")] public sealed class DefaultMemberAnnotation : FixedAttributeValueAnnotationBase { public DefaultMemberAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.DefaultMember, qualifiedSelection, context) + : base(qualifiedSelection, context) { Description = parameters?.FirstOrDefault() ?? string.Empty; } diff --git a/Rubberduck.Parsing/Annotations/DescriptionAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/DescriptionAnnotation.cs similarity index 73% rename from Rubberduck.Parsing/Annotations/DescriptionAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/DescriptionAnnotation.cs index d3e7e716f4..70d42d4b58 100644 --- a/Rubberduck.Parsing/Annotations/DescriptionAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/DescriptionAnnotation.cs @@ -7,10 +7,12 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for specifying a member's VB_Description attribute. /// + [Annotation("Description", AnnotationTarget.Member)] + [FlexibleAttributeValueAnnotation("VB_Description", 1)] public sealed class DescriptionAnnotation : DescriptionAttributeAnnotationBase { public DescriptionAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.Description, qualifiedSelection, context, parameters) + : base(qualifiedSelection, context, parameters) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/DescriptionAttributeAnnotationBase.cs b/Rubberduck.Parsing/Annotations/Implementations/DescriptionAttributeAnnotationBase.cs similarity index 68% rename from Rubberduck.Parsing/Annotations/DescriptionAttributeAnnotationBase.cs rename to Rubberduck.Parsing/Annotations/Implementations/DescriptionAttributeAnnotationBase.cs index 0d3cf59268..da27b85509 100644 --- a/Rubberduck.Parsing/Annotations/DescriptionAttributeAnnotationBase.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/DescriptionAttributeAnnotationBase.cs @@ -7,8 +7,8 @@ namespace Rubberduck.Parsing.Annotations { public abstract class DescriptionAttributeAnnotationBase : FlexibleAttributeValueAnnotationBase { - public DescriptionAttributeAnnotationBase(AnnotationType annotationType, QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable attributeValues) - : base(annotationType, qualifiedSelection, context, attributeValues?.Take(1).ToList()) + public DescriptionAttributeAnnotationBase(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable attributeValues) + : base(qualifiedSelection, context, attributeValues?.Take(1).ToList()) { Description = AttributeValues?.FirstOrDefault(); if ((Description?.StartsWith("\"") ?? false) && Description.EndsWith("\"")) diff --git a/Rubberduck.Parsing/Annotations/EnumeratorMemberAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/EnumeratorMemberAnnotation.cs similarity index 75% rename from Rubberduck.Parsing/Annotations/EnumeratorMemberAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/EnumeratorMemberAnnotation.cs index 8f20e49450..4b5af09ac3 100644 --- a/Rubberduck.Parsing/Annotations/EnumeratorMemberAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/EnumeratorMemberAnnotation.cs @@ -7,10 +7,12 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for specifying a member's VB_UserMemId attribute value. /// + [Annotation("Enumerator", AnnotationTarget.Member)] + [FixedAttributeValueAnnotation("VB_UserMemId", "-4")] public sealed class EnumeratorMemberAnnotation : FixedAttributeValueAnnotationBase { public EnumeratorMemberAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.Enumerator, qualifiedSelection, context) + : base(qualifiedSelection, context) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/ExcelHotKeyAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ExcelHotKeyAnnotation.cs new file mode 100644 index 0000000000..5a65682db9 --- /dev/null +++ b/Rubberduck.Parsing/Annotations/Implementations/ExcelHotKeyAnnotation.cs @@ -0,0 +1,24 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using Rubberduck.Common; +using Rubberduck.Parsing.Grammar; +using Rubberduck.VBEditor; + +namespace Rubberduck.Parsing.Annotations +{ + [Annotation("ExcelHotkey", AnnotationTarget.Member)] + [FlexibleAttributeValueAnnotation("VB_ProcData.VB_Invoke_Func", 1, true)] + public sealed class ExcelHotKeyAnnotation : FlexibleAttributeValueAnnotationBase + { + public ExcelHotKeyAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable annotationParameterValues) : + base(qualifiedSelection, context, GetHotKeyAttributeValue(annotationParameterValues)) + { } + + private static IEnumerable GetHotKeyAttributeValue(IEnumerable parameters) => + parameters.Take(1).Select(v => v.UnQuote()[0] + @"\n14".EnQuote()).ToList(); + + public static IEnumerable TransformToAnnotationValues(IEnumerable attributeValues) => + attributeValues.Select(keySpec => keySpec.UnQuote().Substring(0, 1)); + } +} diff --git a/Rubberduck.Parsing/Annotations/ExposedModuleAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ExposedModuleAnnotation.cs similarity index 75% rename from Rubberduck.Parsing/Annotations/ExposedModuleAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/ExposedModuleAnnotation.cs index d97396da59..490d9d4116 100644 --- a/Rubberduck.Parsing/Annotations/ExposedModuleAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/ExposedModuleAnnotation.cs @@ -7,10 +7,12 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for specifying a module's VB_Exposed attribute. /// + [Annotation("Exposed", AnnotationTarget.Module)] + [FixedAttributeValueAnnotation("VB_Exposed", "True")] public sealed class ExposedModuleAnnotation : FixedAttributeValueAnnotationBase { public ExposedModuleAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.Exposed, qualifiedSelection, context) + : base(qualifiedSelection, context) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/FixedAttributeValueAnnotationBase.cs b/Rubberduck.Parsing/Annotations/Implementations/FixedAttributeValueAnnotationBase.cs new file mode 100644 index 0000000000..b01d7fa7ba --- /dev/null +++ b/Rubberduck.Parsing/Annotations/Implementations/FixedAttributeValueAnnotationBase.cs @@ -0,0 +1,36 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using Rubberduck.Parsing.Grammar; +using Rubberduck.VBEditor; + +namespace Rubberduck.Parsing.Annotations +{ + public abstract class FixedAttributeValueAnnotationBase : AnnotationBase, IAttributeAnnotation + { + protected FixedAttributeValueAnnotationBase(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context) + : base(qualifiedSelection, context) + { + var fixedAttributeValueInfo = FixedAttributeValueInfo(GetType()); + + Attribute = fixedAttributeValueInfo.attribute; + AttributeValues = fixedAttributeValueInfo.attributeValues; + } + + public string Attribute { get; } + public IReadOnlyList AttributeValues { get; } + + private static (string attribute, IReadOnlyList attributeValues) FixedAttributeValueInfo(Type annotationType) + { + var attributeValueInfo = annotationType.GetCustomAttributes(false) + .OfType() + .SingleOrDefault(); + if (attributeValueInfo == null) + { + return ("", new List()); + } + + return (attributeValueInfo.AttributeName, attributeValueInfo.AttributeValues); + } + } +} \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/FlexibleAttributeAnnotationBase.cs b/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeAnnotationBase.cs similarity index 68% rename from Rubberduck.Parsing/Annotations/FlexibleAttributeAnnotationBase.cs rename to Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeAnnotationBase.cs index cdfbd17dce..49d9ca1a40 100644 --- a/Rubberduck.Parsing/Annotations/FlexibleAttributeAnnotationBase.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeAnnotationBase.cs @@ -7,8 +7,8 @@ namespace Rubberduck.Parsing.Annotations { public abstract class FlexibleAttributeAnnotationBase : AnnotationBase, IAttributeAnnotation { - protected FlexibleAttributeAnnotationBase(AnnotationType annotationType, QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IReadOnlyList parameters) - :base(annotationType, qualifiedSelection, context) + protected FlexibleAttributeAnnotationBase(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IReadOnlyList parameters) + :base(qualifiedSelection, context) { Attribute = parameters?.FirstOrDefault() ?? string.Empty; AttributeValues = parameters?.Skip(1).ToList() ?? new List(); diff --git a/Rubberduck.Parsing/Annotations/FlexibleAttributeValueAnnotationBase.cs b/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeValueAnnotationBase.cs similarity index 53% rename from Rubberduck.Parsing/Annotations/FlexibleAttributeValueAnnotationBase.cs rename to Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeValueAnnotationBase.cs index 2e00bd8e6d..1a8d5e3bc8 100644 --- a/Rubberduck.Parsing/Annotations/FlexibleAttributeValueAnnotationBase.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeValueAnnotationBase.cs @@ -11,30 +11,26 @@ public abstract class FlexibleAttributeValueAnnotationBase : AnnotationBase, IAt public string Attribute { get; } public IReadOnlyList AttributeValues { get; } - protected FlexibleAttributeValueAnnotationBase(AnnotationType annotationType, QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable attributeValues) - :base(annotationType, qualifiedSelection, context) + protected FlexibleAttributeValueAnnotationBase(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable attributeValues) + :base(qualifiedSelection, context) { - var flexibleAttributeValueInfo = FlexibleAttributeValueInfo(annotationType); + var flexibleAttributeValueInfo = FlexibleAttributeValueInfo(GetType()); Attribute = flexibleAttributeValueInfo.attribute; AttributeValues = attributeValues?.Take(flexibleAttributeValueInfo.numberOfValues).ToList() ?? new List(); } - private static (string attribute, int numberOfValues) FlexibleAttributeValueInfo(AnnotationType annotationType) + private static (string attribute, int numberOfValues) FlexibleAttributeValueInfo(Type annotationType) { - var type = annotationType.GetType(); - var name = Enum.GetName(type, annotationType); - var flexibleAttributeValueAttributes = type.GetField(name).GetCustomAttributes(false) - .OfType().ToList(); + var attributeValueInfo = annotationType.GetCustomAttributes(false) + .OfType() + .SingleOrDefault(); - var attribute = flexibleAttributeValueAttributes.FirstOrDefault(); - - if (attribute == null) + if (attributeValueInfo == null) { return ("", 0); } - - return (attribute.AttributeName, attribute.NumberOfParameters); + return (attributeValueInfo.AttributeName, attributeValueInfo.NumberOfParameters); } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/FolderAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/FolderAnnotation.cs similarity index 87% rename from Rubberduck.Parsing/Annotations/FolderAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/FolderAnnotation.cs index 59e0d8d43b..b11a512f2b 100644 --- a/Rubberduck.Parsing/Annotations/FolderAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/FolderAnnotation.cs @@ -8,13 +8,14 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for specifying the Code Explorer folder a appears under. /// + [Annotation("Folder", AnnotationTarget.Module)] public sealed class FolderAnnotation : AnnotationBase { public FolderAnnotation( QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.Folder, qualifiedSelection, context) + : base(qualifiedSelection, context) { FolderName = parameters.FirstOrDefault() ?? string.Empty; } diff --git a/Rubberduck.Parsing/Annotations/IgnoreAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/IgnoreAnnotation.cs similarity index 60% rename from Rubberduck.Parsing/Annotations/IgnoreAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/IgnoreAnnotation.cs index 1d69cbcd86..c4972dd371 100644 --- a/Rubberduck.Parsing/Annotations/IgnoreAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/IgnoreAnnotation.cs @@ -8,31 +8,28 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for ignoring specific inspection results from a specified set of inspections. /// + [Annotation("Ignore", AnnotationTarget.General, true)] public sealed class IgnoreAnnotation : AnnotationBase { - private readonly IEnumerable _inspectionNames; - public IgnoreAnnotation( QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.Ignore, qualifiedSelection, context) + : base(qualifiedSelection, context) { - _inspectionNames = parameters; + InspectionNames = parameters; } - public IEnumerable InspectionNames => _inspectionNames; + public IEnumerable InspectionNames { get; } public bool IsIgnored(string inspectionName) { - return _inspectionNames.Contains(inspectionName); + return InspectionNames.Contains(inspectionName); } - public override bool AllowMultiple { get; } = true; - public override string ToString() { - return $"Ignored inspections: {string.Join(", ", _inspectionNames)}"; + return $"Ignored inspections: {string.Join(", ", InspectionNames)}"; } } } diff --git a/Rubberduck.Parsing/Annotations/IgnoreModuleAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/IgnoreModuleAnnotation.cs similarity index 76% rename from Rubberduck.Parsing/Annotations/IgnoreModuleAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/IgnoreModuleAnnotation.cs index c553e28498..670e49af2c 100644 --- a/Rubberduck.Parsing/Annotations/IgnoreModuleAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/IgnoreModuleAnnotation.cs @@ -5,10 +5,14 @@ namespace Rubberduck.Parsing.Annotations { + /// + /// This annotation allows ignoring inspection results of defined inspections for a whole module + /// + [Annotation("IgnoreModule", AnnotationTarget.Module, true)] public sealed class IgnoreModuleAnnotation : AnnotationBase { public IgnoreModuleAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.IgnoreModule, qualifiedSelection, context) + : base(qualifiedSelection, context) { InspectionNames = parameters; } @@ -20,8 +24,6 @@ public bool IsIgnored(string inspectionName) return !InspectionNames.Any() || InspectionNames.Contains(inspectionName); } - public override bool AllowMultiple { get; } = true; - public override string ToString() { return $"Ignored inspections: {string.Join(", ", InspectionNames)}"; diff --git a/Rubberduck.Parsing/Annotations/IgnoreTestAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/IgnoreTestAnnotation.cs similarity index 82% rename from Rubberduck.Parsing/Annotations/IgnoreTestAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/IgnoreTestAnnotation.cs index 365884c71b..f3792d7ba9 100644 --- a/Rubberduck.Parsing/Annotations/IgnoreTestAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/IgnoreTestAnnotation.cs @@ -7,10 +7,11 @@ namespace Rubberduck.Parsing.Annotations /// /// Used to indicate the test engine that a unit test is to be ignored. /// + [Annotation("IgnoreTest", AnnotationTarget.Member)] public sealed class IgnoreTestAnnotation : AnnotationBase { public IgnoreTestAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.IgnoreTest, qualifiedSelection, context) + : base(qualifiedSelection, context) { } } diff --git a/Rubberduck.Parsing/Annotations/InterfaceAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/InterfaceAnnotation.cs similarity index 84% rename from Rubberduck.Parsing/Annotations/InterfaceAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/InterfaceAnnotation.cs index 2c6dc33458..b9c020cbc6 100644 --- a/Rubberduck.Parsing/Annotations/InterfaceAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/InterfaceAnnotation.cs @@ -7,10 +7,11 @@ namespace Rubberduck.Parsing.Annotations /// /// Used to mark a class module as an interface, so that Rubberduck treats it as such even if it's not implemented in any opened project. /// + [Annotation("Interface", AnnotationTarget.Module)] public sealed class InterfaceAnnotation : AnnotationBase { public InterfaceAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.Interface, qualifiedSelection, context) + : base(qualifiedSelection, context) { } } diff --git a/Rubberduck.Parsing/Annotations/Implementations/MemberAttributeAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/MemberAttributeAnnotation.cs new file mode 100644 index 0000000000..d1b88de08a --- /dev/null +++ b/Rubberduck.Parsing/Annotations/Implementations/MemberAttributeAnnotation.cs @@ -0,0 +1,23 @@ +using System.Collections.Generic; +using Rubberduck.Parsing.Grammar; +using Rubberduck.VBEditor; + +namespace Rubberduck.Parsing.Annotations +{ + /// + /// This annotation allows the specification of arbitrary VB_Attribute entries for members. + /// + /// + /// It is disjoint from ModuleAttributeAnnotation because of annotation scoping shenanigans. + /// + // marked as Variable annotation to accomodate annotations of constants + // FIXME consider whether type hierarchy is sufficient to mark as Attribute annotation + // FIXME considre whether this annotation (and ModuleAttribute) should be allowed multiple times + [Annotation("MemberAttribute", AnnotationTarget.Member | AnnotationTarget.Variable)] + public class MemberAttributeAnnotation : FlexibleAttributeAnnotationBase + { + public MemberAttributeAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IReadOnlyList parameters) + :base(qualifiedSelection, context, parameters) + {} + } +} \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/ModuleAttributeAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ModuleAttributeAnnotation.cs similarity index 53% rename from Rubberduck.Parsing/Annotations/ModuleAttributeAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/ModuleAttributeAnnotation.cs index dddd00c0d3..75977efcdc 100644 --- a/Rubberduck.Parsing/Annotations/ModuleAttributeAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/ModuleAttributeAnnotation.cs @@ -4,10 +4,15 @@ namespace Rubberduck.Parsing.Annotations { + /// + /// This annotation allows specifying arbitrary VB_Attribute entries. + /// + // FIXME Consider whether the type-hierarchy alone is sufficient to mark this as an Attribute-Annotation + [Annotation("ModuleAttribute", AnnotationTarget.Module)] public class ModuleAttributeAnnotation : FlexibleAttributeAnnotationBase { public ModuleAttributeAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IReadOnlyList parameters) - :base(AnnotationType.ModuleAttribute, qualifiedSelection, context, parameters) + :base(qualifiedSelection, context, parameters) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/ModuleCleanupAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ModuleCleanupAnnotation.cs similarity index 84% rename from Rubberduck.Parsing/Annotations/ModuleCleanupAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/ModuleCleanupAnnotation.cs index 6de5aca5a4..8f121d3770 100644 --- a/Rubberduck.Parsing/Annotations/ModuleCleanupAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/ModuleCleanupAnnotation.cs @@ -7,13 +7,14 @@ namespace Rubberduck.Parsing.Annotations /// /// Marks a method that the test engine will execute after all unit tests in a test module have executed. /// + [Annotation("ModuleCleanup", AnnotationTarget.Member)] public sealed class ModuleCleanupAnnotation : AnnotationBase { public ModuleCleanupAnnotation( QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.ModuleCleanup, qualifiedSelection, context) + : base(qualifiedSelection, context) { } } diff --git a/Rubberduck.Parsing/Annotations/ModuleDescriptionAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ModuleDescriptionAnnotation.cs similarity index 52% rename from Rubberduck.Parsing/Annotations/ModuleDescriptionAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/ModuleDescriptionAnnotation.cs index 3f098856da..74c02de61b 100644 --- a/Rubberduck.Parsing/Annotations/ModuleDescriptionAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/ModuleDescriptionAnnotation.cs @@ -7,10 +7,15 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for specifying a module's VB_Description attribute. /// + /// + /// This is a class distinct from Member and Variable descriptions, because annotation scoping is annoyingly complicated and Rubberduck has a much easier time if module annotations and member annotations don't have the same name. + /// + [Annotation("ModuleDescription", AnnotationTarget.Module)] + [FlexibleAttributeValueAnnotation("VB_Description", 1)] public sealed class ModuleDescriptionAnnotation : DescriptionAttributeAnnotationBase { public ModuleDescriptionAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.ModuleDescription, qualifiedSelection, context, parameters) + : base(qualifiedSelection, context, parameters) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/ModuleInitializeAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ModuleInitializeAnnotation.cs similarity index 84% rename from Rubberduck.Parsing/Annotations/ModuleInitializeAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/ModuleInitializeAnnotation.cs index b6492c4fe6..f37fc7aedc 100644 --- a/Rubberduck.Parsing/Annotations/ModuleInitializeAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/ModuleInitializeAnnotation.cs @@ -7,13 +7,14 @@ namespace Rubberduck.Parsing.Annotations /// /// Marks a method that the test engine will execute before executing the first unit test in a test module. /// + [Annotation("ModuleInitialize", AnnotationTarget.Member)] public sealed class ModuleInitializeAnnotation : AnnotationBase { public ModuleInitializeAnnotation( QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.ModuleInitialize, qualifiedSelection, context) + : base(qualifiedSelection, context) { } } diff --git a/Rubberduck.Parsing/Annotations/NoIndentAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/NoIndentAnnotation.cs similarity index 82% rename from Rubberduck.Parsing/Annotations/NoIndentAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/NoIndentAnnotation.cs index bc6b3218ec..e788e44ea5 100644 --- a/Rubberduck.Parsing/Annotations/NoIndentAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/NoIndentAnnotation.cs @@ -7,10 +7,11 @@ namespace Rubberduck.Parsing.Annotations /// /// Marks a module that Smart Indenter ignores. /// + [Annotation("NoIndent", AnnotationTarget.Module)] public sealed class NoIndentAnnotation : AnnotationBase { public NoIndentAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.NoIndent, qualifiedSelection, context) + : base(qualifiedSelection, context) { } } diff --git a/Rubberduck.Parsing/Annotations/NotRecognizedAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/NotRecognizedAnnotation.cs similarity index 76% rename from Rubberduck.Parsing/Annotations/NotRecognizedAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/NotRecognizedAnnotation.cs index a5662b05f0..c271b9c0b5 100644 --- a/Rubberduck.Parsing/Annotations/NotRecognizedAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/NotRecognizedAnnotation.cs @@ -6,14 +6,16 @@ namespace Rubberduck.Parsing.Annotations { /// /// Used for all annotations not recognized by RD. + /// Since this is not actually an annotation, it has no valid target /// + [Annotation("NotRecognized", 0)] public sealed class NotRecognizedAnnotation : AnnotationBase { public NotRecognizedAnnotation( QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.NotRecognized, qualifiedSelection, context) + : base(qualifiedSelection, context) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/ObsoleteAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ObsoleteAnnotation.cs similarity index 85% rename from Rubberduck.Parsing/Annotations/ObsoleteAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/ObsoleteAnnotation.cs index 5a2aa449a5..bddea5220f 100644 --- a/Rubberduck.Parsing/Annotations/ObsoleteAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/ObsoleteAnnotation.cs @@ -8,12 +8,13 @@ namespace Rubberduck.Parsing.Annotations /// /// Used to mark members as obsolete, so that Rubberduck can warn users whenever they try to use an obsolete member. /// + [Annotation("Obsolete", AnnotationTarget.Member | AnnotationTarget.Variable)] public sealed class ObsoleteAnnotation : AnnotationBase { public string ReplacementDocumentation { get; } public ObsoleteAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.Obsolete, qualifiedSelection, context) + : base(qualifiedSelection, context) { var firstParameter = parameters.FirstOrDefault(); diff --git a/Rubberduck.Parsing/Annotations/PredeclaredIdAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/PredeclaredIdAnnotation.cs similarity index 74% rename from Rubberduck.Parsing/Annotations/PredeclaredIdAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/PredeclaredIdAnnotation.cs index 1e06ab1392..f4e5c247eb 100644 --- a/Rubberduck.Parsing/Annotations/PredeclaredIdAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/PredeclaredIdAnnotation.cs @@ -7,10 +7,12 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for specifying a module's VB_PredeclaredId attribute. /// + [Annotation("PredeclaredId", AnnotationTarget.Module)] + [FixedAttributeValueAnnotation("VB_PredeclaredId", "True")] public sealed class PredeclaredIdAnnotation : FixedAttributeValueAnnotationBase { public PredeclaredIdAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.PredeclaredId, qualifiedSelection, context) + : base(qualifiedSelection, context) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/TestCleanupAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/TestCleanupAnnotation.cs similarity index 84% rename from Rubberduck.Parsing/Annotations/TestCleanupAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/TestCleanupAnnotation.cs index ccfa38d77c..bfe69a5821 100644 --- a/Rubberduck.Parsing/Annotations/TestCleanupAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/TestCleanupAnnotation.cs @@ -7,13 +7,14 @@ namespace Rubberduck.Parsing.Annotations /// /// Marks a method that the test engine will execute after executing each unit test in a test module. /// + [Annotation("TestCleanup", AnnotationTarget.Member)] public sealed class TestCleanupAnnotation : AnnotationBase { public TestCleanupAnnotation( QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.TestCleanup, qualifiedSelection, context) + : base(qualifiedSelection, context) { } } diff --git a/Rubberduck.Parsing/Annotations/TestInitializeAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/TestInitializeAnnotation.cs similarity index 84% rename from Rubberduck.Parsing/Annotations/TestInitializeAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/TestInitializeAnnotation.cs index f0c28910af..507d62b937 100644 --- a/Rubberduck.Parsing/Annotations/TestInitializeAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/TestInitializeAnnotation.cs @@ -7,13 +7,14 @@ namespace Rubberduck.Parsing.Annotations /// /// Marks a method that the test engine will execute before executing each unit test in a test module. /// + [Annotation("TestInitialize", AnnotationTarget.Member)] public sealed class TestInitializeAnnotation : AnnotationBase { public TestInitializeAnnotation( QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.TestInitialize, qualifiedSelection, context) + : base(qualifiedSelection, context) { } } diff --git a/Rubberduck.Parsing/Annotations/TestMethodAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/TestMethodAnnotation.cs similarity index 77% rename from Rubberduck.Parsing/Annotations/TestMethodAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/TestMethodAnnotation.cs index 28169d70b3..3fc04a8715 100644 --- a/Rubberduck.Parsing/Annotations/TestMethodAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/TestMethodAnnotation.cs @@ -9,14 +9,17 @@ namespace Rubberduck.Parsing.Annotations /// /// Marks a method that the test engine will execute as a unit test. /// + [Annotation("TestMethod", AnnotationTarget.Member)] public sealed class TestMethodAnnotation : AnnotationBase { public TestMethodAnnotation( QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.TestMethod, qualifiedSelection, context) + : base(qualifiedSelection, context) { + // FIXME unify handling of quoted arguments to annotations. + // That should probably be part of VBAParserAnnotationFactory's handling of the annotationArguments context var firstParameter = parameters.FirstOrDefault(); if ((firstParameter?.StartsWith("\"") ?? false) && firstParameter.EndsWith("\"")) { diff --git a/Rubberduck.Parsing/Annotations/TestModuleAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/TestModuleAnnotation.cs similarity index 72% rename from Rubberduck.Parsing/Annotations/TestModuleAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/TestModuleAnnotation.cs index 2ddb717f69..6d34b5d8c6 100644 --- a/Rubberduck.Parsing/Annotations/TestModuleAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/TestModuleAnnotation.cs @@ -10,13 +10,15 @@ namespace Rubberduck.Parsing.Annotations /// /// Unit test discovery only inspects modules with a @TestModule annotation. /// + [Annotation("TestModule", AnnotationTarget.Module)] public sealed class TestModuleAnnotation : AnnotationBase { + // TODO investigate unused parameters argument. Possibly needed to match signature for construction through VBAParserAnnotationFactory?! public TestModuleAnnotation( QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.TestModule, qualifiedSelection, context) + : base(qualifiedSelection, context) { } } diff --git a/Rubberduck.Parsing/Annotations/VariableDescriptionAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/VariableDescriptionAnnotation.cs similarity index 68% rename from Rubberduck.Parsing/Annotations/VariableDescriptionAnnotation.cs rename to Rubberduck.Parsing/Annotations/Implementations/VariableDescriptionAnnotation.cs index 675570b828..ac3397023c 100644 --- a/Rubberduck.Parsing/Annotations/VariableDescriptionAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/VariableDescriptionAnnotation.cs @@ -4,10 +4,12 @@ namespace Rubberduck.Parsing.Annotations { + [Annotation("VariableDescription", AnnotationTarget.Variable)] + [FlexibleAttributeValueAnnotation("VB_VarDescription", 1)] public class VariableDescriptionAnnotation : DescriptionAttributeAnnotationBase { public VariableDescriptionAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(AnnotationType.VariableDescription, qualifiedSelection, context, parameters) + : base(qualifiedSelection, context, parameters) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/MemberAttributeAnnotation.cs b/Rubberduck.Parsing/Annotations/MemberAttributeAnnotation.cs deleted file mode 100644 index 0faffd0e9d..0000000000 --- a/Rubberduck.Parsing/Annotations/MemberAttributeAnnotation.cs +++ /dev/null @@ -1,13 +0,0 @@ -using System.Collections.Generic; -using Rubberduck.Parsing.Grammar; -using Rubberduck.VBEditor; - -namespace Rubberduck.Parsing.Annotations -{ - public class MemberAttributeAnnotation : FlexibleAttributeAnnotationBase - { - public MemberAttributeAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IReadOnlyList parameters) - :base(AnnotationType.MemberAttribute, qualifiedSelection, context, parameters) - {} - } -} \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs b/Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs index 46c8ca27ea..13d104cc85 100644 --- a/Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs +++ b/Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs @@ -10,30 +10,16 @@ public sealed class VBAParserAnnotationFactory : IAnnotationFactory { private readonly Dictionary _creators = new Dictionary(); - public VBAParserAnnotationFactory() + public VBAParserAnnotationFactory(IEnumerable recognizedAnnotationTypes) { - _creators.Add(AnnotationType.TestModule.ToString().ToUpperInvariant(), typeof(TestModuleAnnotation)); - _creators.Add(AnnotationType.ModuleInitialize.ToString().ToUpperInvariant(), typeof(ModuleInitializeAnnotation)); - _creators.Add(AnnotationType.ModuleCleanup.ToString().ToUpperInvariant(), typeof(ModuleCleanupAnnotation)); - _creators.Add(AnnotationType.TestMethod.ToString().ToUpperInvariant(), typeof(TestMethodAnnotation)); - _creators.Add(AnnotationType.TestInitialize.ToString().ToUpperInvariant(), typeof(TestInitializeAnnotation)); - _creators.Add(AnnotationType.TestCleanup.ToString().ToUpperInvariant(), typeof(TestCleanupAnnotation)); - _creators.Add(AnnotationType.Ignore.ToString().ToUpperInvariant(), typeof(IgnoreAnnotation)); - _creators.Add(AnnotationType.IgnoreModule.ToString().ToUpperInvariant(), typeof(IgnoreModuleAnnotation)); - _creators.Add(AnnotationType.IgnoreTest.ToString().ToUpperInvariant(), typeof(IgnoreTestAnnotation)); - _creators.Add(AnnotationType.Folder.ToString().ToUpperInvariant(), typeof(FolderAnnotation)); - _creators.Add(AnnotationType.NoIndent.ToString().ToUpperInvariant(), typeof(NoIndentAnnotation)); - _creators.Add(AnnotationType.Interface.ToString().ToUpperInvariant(), typeof(InterfaceAnnotation)); - _creators.Add(AnnotationType.Description.ToString().ToUpperInvariant(), typeof (DescriptionAnnotation)); - _creators.Add(AnnotationType.PredeclaredId.ToString().ToUpperInvariant(), typeof(PredeclaredIdAnnotation)); - _creators.Add(AnnotationType.DefaultMember.ToString().ToUpperInvariant(), typeof(DefaultMemberAnnotation)); - _creators.Add(AnnotationType.Enumerator.ToString().ToUpperInvariant(), typeof(EnumeratorMemberAnnotation)); - _creators.Add(AnnotationType.Exposed.ToString().ToUpperInvariant(), typeof (ExposedModuleAnnotation)); - _creators.Add(AnnotationType.Obsolete.ToString().ToUpperInvariant(), typeof(ObsoleteAnnotation)); - _creators.Add(AnnotationType.ModuleAttribute.ToString().ToUpperInvariant(), typeof(ModuleAttributeAnnotation)); - _creators.Add(AnnotationType.MemberAttribute.ToString().ToUpperInvariant(), typeof(MemberAttributeAnnotation)); - _creators.Add(AnnotationType.ModuleDescription.ToString().ToUpperInvariant(), typeof(ModuleDescriptionAnnotation)); - _creators.Add(AnnotationType.ExcelHotKey.ToString().ToUpperInvariant(), typeof(ExcelHotKeyAnnotation)); + foreach (var annotationType in recognizedAnnotationTypes) + { + // Extract the static information about the annotation type from it's AnnotationAttribute + var staticInfo = annotationType.GetCustomAttributes(false) + .OfType() + .Single(); + _creators.Add(staticInfo.Name.ToUpperInvariant(), annotationType); + } } public IAnnotation Create(VBAParser.AnnotationContext context, QualifiedSelection qualifiedSelection) @@ -43,16 +29,16 @@ public IAnnotation Create(VBAParser.AnnotationContext context, QualifiedSelectio return CreateAnnotation(annotationName, parameters, qualifiedSelection, context); } - private static List AnnotationParametersFromContext(VBAParser.AnnotationContext context) + private static List AnnotationParametersFromContext(VBAParser.AnnotationContext context) + { + var parameters = new List(); + var argList = context.annotationArgList(); + if (argList != null) { - var parameters = new List(); - var argList = context.annotationArgList(); - if (argList != null) - { - parameters.AddRange(argList.annotationArg().Select(arg => arg.GetText())); - } - return parameters; + parameters.AddRange(argList.annotationArg().Select(arg => arg.GetText())); } + return parameters; + } private IAnnotation CreateAnnotation(string annotationName, IReadOnlyList parameters, QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context) diff --git a/Rubberduck.Parsing/Grammar/PartialExtensions/IAnnotatedContext.cs b/Rubberduck.Parsing/Grammar/PartialExtensions/IAnnotatedContext.cs index a5cb67cb2b..98d8ab42a7 100644 --- a/Rubberduck.Parsing/Grammar/PartialExtensions/IAnnotatedContext.cs +++ b/Rubberduck.Parsing/Grammar/PartialExtensions/IAnnotatedContext.cs @@ -24,6 +24,6 @@ public interface IAnnotatedContext public interface IAnnotatingContext { ParserRuleContext AnnotatedContext { get; } - AnnotationType AnnotationType { get; } + string AnnotationType { get; } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Grammar/PartialExtensions/VBAParserPartialExtensions.cs b/Rubberduck.Parsing/Grammar/PartialExtensions/VBAParserPartialExtensions.cs index 84b06e4a40..10a0258413 100644 --- a/Rubberduck.Parsing/Grammar/PartialExtensions/VBAParserPartialExtensions.cs +++ b/Rubberduck.Parsing/Grammar/PartialExtensions/VBAParserPartialExtensions.cs @@ -15,8 +15,7 @@ public partial class AnnotationContext : IAnnotatingContext { public ParserRuleContext AnnotatedContext { get; internal set; } - public AnnotationType AnnotationType => (AnnotationType) Enum.Parse(typeof (AnnotationType), - Identifier.GetName(this.annotationName().unrestrictedIdentifier())); + public string AnnotationType => Identifier.GetName(this.annotationName().unrestrictedIdentifier()); } public partial class ModuleAttributesContext : IAnnotatedContext // holds module-scoped annotations diff --git a/Rubberduck.Parsing/Rubberduck.Parsing.csproj b/Rubberduck.Parsing/Rubberduck.Parsing.csproj index ccdc888c55..7e91a59e92 100644 --- a/Rubberduck.Parsing/Rubberduck.Parsing.csproj +++ b/Rubberduck.Parsing/Rubberduck.Parsing.csproj @@ -30,6 +30,7 @@ + diff --git a/Rubberduck.Parsing/Symbols/Attributes.cs b/Rubberduck.Parsing/Symbols/Attributes.cs index 653311bf37..f87cefd737 100644 --- a/Rubberduck.Parsing/Symbols/Attributes.cs +++ b/Rubberduck.Parsing/Symbols/Attributes.cs @@ -130,7 +130,7 @@ public bool HasAttributeFor(IAttributeAnnotation annotation, string memberName = public IEnumerable AttributeNodesFor(IAttributeAnnotation annotation, string memberName = null) { - if (!annotation.AnnotationType.HasFlag(AnnotationType.Attribute)) + if (!annotation.GetType().GetInterfaces().Contains(typeof(IAttributeAnnotation))) { return Enumerable.Empty(); } diff --git a/Rubberduck.Parsing/Symbols/ModuleDeclaration.cs b/Rubberduck.Parsing/Symbols/ModuleDeclaration.cs index 7f2d2ccf01..a3439a1198 100644 --- a/Rubberduck.Parsing/Symbols/ModuleDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/ModuleDeclaration.cs @@ -55,7 +55,7 @@ internal void RemoveAnnotations(ICollection annotationsToRemove) private string FolderFromAnnotations() { - var @namespace = Annotations.FirstOrDefault(annotation => annotation.AnnotationType == AnnotationType.Folder); + var @namespace = Annotations.OfType().FirstOrDefault(); string result; if (@namespace == null) { @@ -65,7 +65,7 @@ private string FolderFromAnnotations() } else { - var value = ((FolderAnnotation)@namespace).FolderName; + var value = @namespace.FolderName; result = value; } return result; diff --git a/Rubberduck.Parsing/VBA/AnnotationUpdater.cs b/Rubberduck.Parsing/VBA/AnnotationUpdater.cs index cb0843e1bd..8c77a97e04 100644 --- a/Rubberduck.Parsing/VBA/AnnotationUpdater.cs +++ b/Rubberduck.Parsing/VBA/AnnotationUpdater.cs @@ -17,25 +17,25 @@ public class AnnotationUpdater : IAnnotationUpdater { private readonly Logger _logger = LogManager.GetCurrentClassLogger(); - public void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext context, AnnotationType annotationType, IReadOnlyList values = null) + public void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext context, AnnotationAttribute annotationInfo, IReadOnlyList values = null) { var annotationValues = values ?? new List(); if (context == null) { _logger.Warn("Tried to add an annotation to a context that is null."); - _logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to a context that is null."); + _logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to a context that is null."); return; } if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode) { _logger.Warn($"Tried to add an annotation with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})"); - _logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to {context.Context.GetText()} at {context.Context.GetSelection()} in module {context.ModuleName} using a rewriter not suitable for annotations."); + _logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to {context.Context.GetText()} at {context.Context.GetSelection()} in module {context.ModuleName} using a rewriter not suitable for annotations."); return; } - var annotationText = AnnotationText(annotationType, annotationValues); + var annotationText = AnnotationText(annotationInfo.Name, annotationValues); string codeToAdd; IModuleRewriter rewriter; @@ -57,7 +57,7 @@ public void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext conte if (context.Context.start.Line > previousEndOfLine.stop.Line + 1) { _logger.Warn("Tried to add an annotation to a context not on the first physical line of a logical line."); - _logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to a the context with text '{context.Context.GetText()}' at {context.Context.GetSelection()} in module {context.ModuleName}."); + _logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to a the context with text '{context.Context.GetText()}' at {context.Context.GetSelection()} in module {context.ModuleName}."); return; } @@ -68,12 +68,17 @@ public void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext conte rewriter.InsertAfter(previousEndOfLine.stop.TokenIndex, codeToAdd); } - private static string AnnotationText(AnnotationType annotationType, IReadOnlyList values) + private static string AnnotationText(AnnotationAttribute annotationInformation, IReadOnlyList values) + { + return AnnotationText(annotationInformation.Name, values); + } + + private static string AnnotationText(string annotationType, IReadOnlyList values) { return $"'{AnnotationBase.ANNOTATION_MARKER}{AnnotationBaseText(annotationType, values)}"; } - private static string AnnotationBaseText(AnnotationType annotationType, IReadOnlyList values) + private static string AnnotationBaseText(string annotationType, IReadOnlyList values) { return $"{annotationType}{(values.Any() ? $" {AnnotationValuesText(values)}" : string.Empty)}"; } @@ -94,93 +99,93 @@ private static VBAParser.EndOfLineContext PreviousEndOfLine(ParserRuleContext co return previousEol; } - public void AddAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationType annotationType, IReadOnlyList values = null) + public void AddAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationAttribute annotationInfo, IReadOnlyList values = null) { var annotationValues = values ?? new List(); if (declaration == null) { _logger.Warn("Tried to add an annotation to a declaration that is null."); - _logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to a declaration that is null."); + _logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to a declaration that is null."); return; } if (declaration.DeclarationType.HasFlag(DeclarationType.Module)) { - AddModuleAnnotation(rewriteSession, declaration, annotationType, annotationValues); + AddModuleAnnotation(rewriteSession, declaration, annotationInfo, annotationValues); } else if (declaration.DeclarationType.HasFlag(DeclarationType.Variable)) { - AddVariableAnnotation(rewriteSession, declaration, annotationType, annotationValues); + AddVariableAnnotation(rewriteSession, declaration, annotationInfo, annotationValues); } else { - AddMemberAnnotation(rewriteSession, declaration, annotationType, annotationValues); + AddMemberAnnotation(rewriteSession, declaration, annotationInfo, annotationValues); } } - private void AddModuleAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationType annotationType, IReadOnlyList annotationValues) + private void AddModuleAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationAttribute annotationInfo, IReadOnlyList annotationValues) { - if (!annotationType.HasFlag(AnnotationType.ModuleAnnotation)) + if (!annotationInfo.Target.HasFlag(AnnotationTarget.Module)) { _logger.Warn("Tried to add an annotation without the module annotation flag to a module."); - _logger.Trace($"Tried to add the annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the module {declaration.QualifiedModuleName}."); + _logger.Trace($"Tried to add the annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to the module {declaration.QualifiedModuleName}."); return; } if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode) { _logger.Warn($"Tried to add an annotation to a module with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})"); - _logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the module {declaration.QualifiedModuleName} using a rewriter not suitable for annotations."); + _logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to the module {declaration.QualifiedModuleName} using a rewriter not suitable for annotations."); return; } - var codeToAdd = $"{AnnotationText(annotationType, annotationValues)}{Environment.NewLine}"; + var codeToAdd = $"{AnnotationText(annotationInfo, annotationValues)}{Environment.NewLine}"; var rewriter = rewriteSession.CheckOutModuleRewriter(declaration.QualifiedModuleName); rewriter.InsertBefore(0, codeToAdd); } - private void AddVariableAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationType annotationType, IReadOnlyList annotationValues) + private void AddVariableAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationAttribute annotationInfo, IReadOnlyList annotationValues) { - if (!annotationType.HasFlag(AnnotationType.VariableAnnotation)) + if (!annotationInfo.Target.HasFlag(AnnotationTarget.Variable)) { _logger.Warn("Tried to add an annotation without the variable annotation flag to a variable declaration."); - _logger.Trace($"Tried to add the annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the variable declaration for {declaration.QualifiedName}."); + _logger.Trace($"Tried to add the annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to the variable declaration for {declaration.QualifiedName}."); return; } if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode) { _logger.Warn($"Tried to add an annotation to a variable with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})"); - _logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the the variable {declaration.IdentifierName} at {declaration.Selection} in module {declaration.QualifiedModuleName} using a rewriter not suitable for annotations."); + _logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to the the variable {declaration.IdentifierName} at {declaration.Selection} in module {declaration.QualifiedModuleName} using a rewriter not suitable for annotations."); return; } - AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationType, annotationValues); + AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationInfo, annotationValues); } - private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationType annotationType, IReadOnlyList annotationValues) + private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationAttribute annotationInfo, IReadOnlyList annotationValues) { - if (!annotationType.HasFlag(AnnotationType.MemberAnnotation)) + if (!annotationInfo.Target.HasFlag(AnnotationTarget.Member)) { _logger.Warn("Tried to add an annotation without the member annotation flag to a member declaration."); - _logger.Trace($"Tried to add the annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the member declaration for {declaration.QualifiedName}."); + _logger.Trace($"Tried to add the annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to the member declaration for {declaration.QualifiedName}."); return; } if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode) { _logger.Warn($"Tried to add an annotation to a member with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})"); - _logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the the member {declaration.IdentifierName} at {declaration.Selection} in module {declaration.QualifiedModuleName} using a rewriter not suitable for annotations."); + _logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to the the member {declaration.IdentifierName} at {declaration.Selection} in module {declaration.QualifiedModuleName} using a rewriter not suitable for annotations."); return; } - AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationType, annotationValues); + AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationInfo, annotationValues); } - public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, AnnotationType annotationType, + public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, AnnotationAttribute annotationInfo, IReadOnlyList values = null) { var annotationValues = values ?? new List(); @@ -188,25 +193,25 @@ private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration dec if (reference == null) { _logger.Warn("Tried to add an annotation to an identifier reference that is null."); - _logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to an identifier reference that is null."); + _logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to an identifier reference that is null."); return; } - if (!annotationType.HasFlag(AnnotationType.IdentifierAnnotation)) + if (!annotationInfo.Target.HasFlag(AnnotationTarget.Identifier)) { _logger.Warn("Tried to add an annotation without the identifier reference annotation flag to an identifier reference."); - _logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the identifier reference to {reference.Declaration.QualifiedName} at {reference.Selection} in module {reference.QualifiedModuleName}."); + _logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to the identifier reference to {reference.Declaration.QualifiedName} at {reference.Selection} in module {reference.QualifiedModuleName}."); return; } if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode) { _logger.Warn($"Tried to add an annotation to an identifier reference with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})"); - _logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the the identifier reference {reference.IdentifierName} at {reference.Selection} in module {reference.QualifiedModuleName} using a rewriter not suitable for annotations."); + _logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to the the identifier reference {reference.IdentifierName} at {reference.Selection} in module {reference.QualifiedModuleName} using a rewriter not suitable for annotations."); return; } - AddAnnotation(rewriteSession, new QualifiedContext(reference.QualifiedModuleName, reference.Context), annotationType, annotationValues); + AddAnnotation(rewriteSession, new QualifiedContext(reference.QualifiedModuleName, reference.Context), annotationInfo, annotationValues); } public void RemoveAnnotation(IRewriteSession rewriteSession, IAnnotation annotation) @@ -325,35 +330,35 @@ public void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable newValues = null) + public void UpdateAnnotation(IRewriteSession rewriteSession, IAnnotation annotation, AnnotationAttribute annotationInfo, IReadOnlyList newValues = null) { var newAnnotationValues = newValues ?? new List(); if (annotation == null) { _logger.Warn("Tried to replace an annotation that is null."); - _logger.Trace($"Tried to replace an annotation that is null with an annotation {newAnnotationType} with values {AnnotationValuesText(newAnnotationValues)}."); + _logger.Trace($"Tried to replace an annotation that is null with an annotation {annotationInfo.Name} with values {AnnotationValuesText(newAnnotationValues)}."); return; } if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode) { _logger.Warn($"Tried to update an annotation with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})"); - _logger.Trace($"Tried to update annotation {annotation.AnnotationType} at {annotation.QualifiedSelection.Selection} in module {annotation.QualifiedSelection.QualifiedName} with annotation {newAnnotationType} with values {AnnotationValuesText(newAnnotationValues)} using a rewriter not suitable for annotations."); + _logger.Trace($"Tried to update annotation {annotation.AnnotationType} at {annotation.QualifiedSelection.Selection} in module {annotation.QualifiedSelection.QualifiedName} with annotation {annotationInfo.Name} with values {AnnotationValuesText(newAnnotationValues)} using a rewriter not suitable for annotations."); return; } //If there are no common flags, the annotations cannot apply to the same target. - if ((annotation.AnnotationType & newAnnotationType) == 0) + if ((annotation.MetaInformation.Target & annotationInfo.Target) == 0) { _logger.Warn("Tried to replace an annotation with an annotation without common flags."); - _logger.Trace($"Tried to replace an annotation {annotation.AnnotationType} with values {AnnotationValuesText(newValues)} at {annotation.QualifiedSelection.Selection} in module {annotation.QualifiedSelection.QualifiedName} with an annotation {newAnnotationType} with values {AnnotationValuesText(newAnnotationValues)}, which does not have any common flags."); + _logger.Trace($"Tried to replace an annotation {annotation.AnnotationType} with values {AnnotationValuesText(newValues)} at {annotation.QualifiedSelection.Selection} in module {annotation.QualifiedSelection.QualifiedName} with an annotation {annotationInfo.Name} with values {AnnotationValuesText(newAnnotationValues)}, which does not have any common flags."); return; } var context = annotation.Context; var whitespaceAtEnd = context.whiteSpace()?.GetText() ?? string.Empty; - var codeReplacement = $"{AnnotationBaseText(newAnnotationType, newAnnotationValues)}{whitespaceAtEnd}"; + var codeReplacement = $"{AnnotationBaseText(annotationInfo.Name, newAnnotationValues)}{whitespaceAtEnd}"; var rewriter = rewriteSession.CheckOutModuleRewriter(annotation.QualifiedSelection.QualifiedName); rewriter.Replace(annotation.Context, codeReplacement); diff --git a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs index de250d2443..84d65b6127 100644 --- a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs +++ b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs @@ -550,6 +550,12 @@ public IEnumerable FindAnnotations(QualifiedModuleName module, int : Enumerable.Empty(); } + public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine, AnnotationTarget target) + { + return FindAnnotations(module, annotatedLine) + .Where(annot => annot.MetaInformation.Target.HasFlag(target)); + } + public bool IsMatch(string declarationName, string potentialMatchName) { return string.Equals(declarationName, potentialMatchName, StringComparison.OrdinalIgnoreCase); @@ -972,11 +978,8 @@ public Declaration FindMemberEnclosingProcedure(Declaration enclosingProcedure, public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string identifierName, ParserRuleContext context) { - var annotations = FindAnnotations(enclosingProcedure.QualifiedName.QualifiedModuleName, context.Start.Line) - .Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation)); - + var annotations = FindAnnotations(enclosingProcedure.QualifiedName.QualifiedModuleName, context.Start.Line,AnnotationTarget.Identifier); var isReDimVariable = IsContainedInReDimedArrayName(context); - var undeclaredLocal = new Declaration( new QualifiedMemberName(enclosingProcedure.QualifiedName.QualifiedModuleName, identifierName), @@ -1038,8 +1041,7 @@ public void AddUnboundContext(Declaration parentDeclaration, VBAParser.LExpressi } var identifier = context.GetChild(0); - var annotations = FindAnnotations(parentDeclaration.QualifiedName.QualifiedModuleName, context.Start.Line) - .Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation)); + var annotations = FindAnnotations(parentDeclaration.QualifiedName.QualifiedModuleName, context.Start.Line, AnnotationTarget.Identifier); var declaration = new UnboundMemberDeclaration(parentDeclaration, identifier, (context is VBAParser.MemberAccessExprContext) ? (ParserRuleContext)context.children[0] : withExpression.Context, diff --git a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs index 63a73ca84f..d025eb3321 100644 --- a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs +++ b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs @@ -244,14 +244,14 @@ private static IEnumerable FindModuleAnnotations(IParseTree tree, I if (firstModuleBodyLine == null) { return annotationsOnWhiteSpaceLines.Values.SelectMany(annotationList => annotationList) - .Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.ModuleAnnotation)); + .Where(annotation => annotation.MetaInformation.Target.HasFlag(AnnotationTarget.Module)); } var lastPossibleAnnotatedLine = firstModuleBodyLine.Value; var moduleAnnotations = annotationsOnWhiteSpaceLines.Keys .Where(line => (line <= lastPossibleAnnotatedLine)) .SelectMany(line => annotationsOnWhiteSpaceLines[line]) - .Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.ModuleAnnotation)); + .Where(annotation => annotation.MetaInformation.Target.HasFlag(AnnotationTarget.Module)); return moduleAnnotations; } diff --git a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs index d7ff1e4652..bcd77812f3 100644 --- a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs +++ b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs @@ -44,10 +44,10 @@ public class DeclarationSymbolsListener : VBAParserBaseListener private IEnumerable FindMemberAnnotations(int firstMemberLine) { - return FindAnnotations(firstMemberLine, AnnotationType.MemberAnnotation); + return FindAnnotations(firstMemberLine, AnnotationTarget.Member); } - private IEnumerable FindAnnotations(int firstLine, AnnotationType annotationTypeFlag) + private IEnumerable FindAnnotations(int firstLine, AnnotationTarget requiredTarget) { if (_annotations == null) { @@ -56,7 +56,7 @@ private IEnumerable FindAnnotations(int firstLine, AnnotationType a if (_annotations.TryGetValue(firstLine, out var scopedAnnotations)) { - return scopedAnnotations.Where(annotation => annotation.AnnotationType.HasFlag(annotationTypeFlag)); + return scopedAnnotations.Where(annotation => annotation.MetaInformation.Target.HasFlag(requiredTarget)); } return Enumerable.Empty(); @@ -64,12 +64,12 @@ private IEnumerable FindAnnotations(int firstLine, AnnotationType a private IEnumerable FindVariableAnnotations(int firstVariableLine) { - return FindAnnotations(firstVariableLine, AnnotationType.VariableAnnotation); + return FindAnnotations(firstVariableLine, AnnotationTarget.Variable); } private IEnumerable FindGeneralAnnotations(int firstLine) { - return FindAnnotations(firstLine, AnnotationType.GeneralAnnotation); + return FindAnnotations(firstLine, AnnotationTarget.General); } private Declaration CreateDeclaration( diff --git a/Rubberduck.Parsing/VBA/IAnnotationUpdater.cs b/Rubberduck.Parsing/VBA/IAnnotationUpdater.cs index 3d53026384..0c9e27dbb8 100644 --- a/Rubberduck.Parsing/VBA/IAnnotationUpdater.cs +++ b/Rubberduck.Parsing/VBA/IAnnotationUpdater.cs @@ -8,11 +8,11 @@ namespace Rubberduck.Parsing.VBA { public interface IAnnotationUpdater { - void AddAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationType annotationType, IReadOnlyList values = null); - void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, AnnotationType annotationType, IReadOnlyList values = null); - void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext context, AnnotationType annotationType, IReadOnlyList values = null); + void AddAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationAttribute newAnnotation, IReadOnlyList values = null); + void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, AnnotationAttribute newAnnotation, IReadOnlyList values = null); + void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext context, AnnotationAttribute newAnnotation, IReadOnlyList values = null); void RemoveAnnotation(IRewriteSession rewriteSession, IAnnotation annotation); void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable annotations); - void UpdateAnnotation(IRewriteSession rewriteSession, IAnnotation annotation, AnnotationType newAnnotationType, IReadOnlyList newValues = null); + void UpdateAnnotation(IRewriteSession rewriteSession, IAnnotation oldAnnotation, AnnotationAttribute newAnnotation, IReadOnlyList newValues = null); } } \ No newline at end of file diff --git a/Rubberduck.Parsing/VBA/Parsing/ModuleParser.cs b/Rubberduck.Parsing/VBA/Parsing/ModuleParser.cs index 79021eecbd..f0d68f88bd 100644 --- a/Rubberduck.Parsing/VBA/Parsing/ModuleParser.cs +++ b/Rubberduck.Parsing/VBA/Parsing/ModuleParser.cs @@ -22,14 +22,16 @@ public class ModuleParser : IModuleParser private readonly ISourceCodeProvider _codePaneSourceCodeProvider; private readonly ISourceCodeProvider _attributesSourceCodeProvider; private readonly IStringParser _parser; + private readonly IAnnotationFactory _annotationFactory; private static readonly Logger Logger = LogManager.GetCurrentClassLogger(); - public ModuleParser(ISourceCodeProvider codePaneSourceCodeProvider, ISourceCodeProvider attributesSourceCodeProvider, IStringParser parser) + public ModuleParser(ISourceCodeProvider codePaneSourceCodeProvider, ISourceCodeProvider attributesSourceCodeProvider, IStringParser parser, IAnnotationFactory annotationFactory) { _codePaneSourceCodeProvider = codePaneSourceCodeProvider; _attributesSourceCodeProvider = attributesSourceCodeProvider; _parser = parser; + _annotationFactory = annotationFactory; } public ModuleParseResults Parse(QualifiedModuleName module, CancellationToken cancellationToken, TokenStreamRewriter rewriter = null) @@ -120,7 +122,7 @@ private ModuleParseResults ParseInternal(QualifiedModuleName module, Cancellatio private (IEnumerable Comments, IEnumerable Annotations) CommentsAndAnnotations(QualifiedModuleName module, IParseTree tree) { var commentListener = new CommentListener(); - var annotationListener = new AnnotationListener(new VBAParserAnnotationFactory(), module); + var annotationListener = new AnnotationListener(_annotationFactory, module); var combinedListener = new CombinedParseTreeListener(new IParseTreeListener[] {commentListener, annotationListener}); ParseTreeWalker.Default.Walk(combinedListener, tree); var comments = QualifyAndUnionComments(module, commentListener.Comments, commentListener.RemComments); diff --git a/Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs b/Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs index 164660a07e..41c9667abc 100644 --- a/Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs +++ b/Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs @@ -133,8 +133,7 @@ public BoundExpressionVisitor(DeclarationFinder declarationFinder) private IEnumerable FindIdentifierAnnotations(QualifiedModuleName module, int line) { - return _declarationFinder.FindAnnotations(module, line) - .Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation)); + return _declarationFinder.FindAnnotations(module, line, AnnotationTarget.Identifier); } private void Visit( diff --git a/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs b/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs index e0c0ec64f8..e0f6808139 100644 --- a/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs +++ b/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs @@ -163,7 +163,7 @@ private void ResolveLabel(ParserRuleContext context, string label) private IEnumerable FindIdentifierAnnotations(QualifiedModuleName module, int line) { return _declarationFinder.FindAnnotations(module, line) - .Where(annotation => annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation)); + .Where(annotation => annotation.MetaInformation.Target.HasFlag(AnnotationTarget.Identifier)); } private void ResolveDefault( diff --git a/Rubberduck.Parsing/VBA/RubberduckParserState.cs b/Rubberduck.Parsing/VBA/RubberduckParserState.cs index 21e699e234..f6706cda72 100644 --- a/Rubberduck.Parsing/VBA/RubberduckParserState.cs +++ b/Rubberduck.Parsing/VBA/RubberduckParserState.cs @@ -189,9 +189,9 @@ public RubberduckParserState(IVBE vbe, IProjectsRepository projectRepository, ID private void RefreshFinder(IHostApplication host) { - var oldDecalarationFinder = DeclarationFinder; + var oldDeclarationFinder = DeclarationFinder; DeclarationFinder = _declarationFinderFactory.Create(AllDeclarationsFromModuleStates, AllAnnotations, AllUnresolvedMemberDeclarationsFromModulestates, AllUnboundDefaultMemberAccessesFromModuleStates, host); - _declarationFinderFactory.Release(oldDecalarationFinder); + _declarationFinderFactory.Release(oldDeclarationFinder); } public void RefreshDeclarationFinder() diff --git a/Rubberduck.UnitTesting/UnitTesting/TestDiscovery.cs b/Rubberduck.UnitTesting/UnitTesting/TestDiscovery.cs index 8d731dc1ae..f1d8701130 100644 --- a/Rubberduck.UnitTesting/UnitTesting/TestDiscovery.cs +++ b/Rubberduck.UnitTesting/UnitTesting/TestDiscovery.cs @@ -37,7 +37,7 @@ public static bool IsTestMethod(RubberduckParserState state, Declaration item) { return !state.AllUserDeclarations.Any(d => d.DeclarationType == DeclarationType.Parameter && Equals(d.ParentScopeDeclaration, item)) && - item.Annotations.Any(a => a.AnnotationType == AnnotationType.TestMethod); + item.Annotations.OfType().Any(); } public static IEnumerable FindModuleInitializeMethods(QualifiedModuleName module, RubberduckParserState state) @@ -45,7 +45,7 @@ public static IEnumerable FindModuleInitializeMethods(QualifiedModu return GetTestModuleProcedures(state) .Where(m => m.QualifiedName.QualifiedModuleName == module && - m.Annotations.Any(a => a.AnnotationType == AnnotationType.ModuleInitialize)); + m.Annotations.OfType().Any()); } public static IEnumerable FindModuleCleanupMethods(QualifiedModuleName module, RubberduckParserState state) @@ -53,7 +53,7 @@ public static IEnumerable FindModuleCleanupMethods(QualifiedModuleN return GetTestModuleProcedures(state) .Where(m => m.QualifiedName.QualifiedModuleName == module && - m.Annotations.Any(a => a.AnnotationType == AnnotationType.ModuleCleanup)); + m.Annotations.OfType().Any()); } public static IEnumerable FindTestInitializeMethods(QualifiedModuleName module, RubberduckParserState state) @@ -61,7 +61,7 @@ public static IEnumerable FindTestInitializeMethods(QualifiedModule return GetTestModuleProcedures(state) .Where(m => m.QualifiedName.QualifiedModuleName == module && - m.Annotations.Any(a => a.AnnotationType == AnnotationType.TestInitialize)); + m.Annotations.OfType().Any()); } public static IEnumerable FindTestCleanupMethods(QualifiedModuleName module, RubberduckParserState state) @@ -69,7 +69,7 @@ public static IEnumerable FindTestCleanupMethods(QualifiedModuleNam return GetTestModuleProcedures(state) .Where(m => m.QualifiedName.QualifiedModuleName == module && - m.Annotations.Any(a => a.AnnotationType == AnnotationType.TestCleanup)); + m.Annotations.OfType().Any()); } private static IEnumerable GetTestModuleProcedures(RubberduckParserState state) @@ -78,14 +78,14 @@ private static IEnumerable GetTestModuleProcedures(RubberduckParser return procedures.Where(item => item.ParentDeclaration.DeclarationType == DeclarationType.ProceduralModule && - item.ParentDeclaration.Annotations.Any(a => a.AnnotationType == AnnotationType.TestModule)); + item.ParentDeclaration.Annotations.OfType().Any()); } public static IEnumerable GetTestModules(this RubberduckParserState state) { return state.AllUserDeclarations.Where(item => item.DeclarationType == DeclarationType.ProceduralModule && - item.Annotations.Any(a => a.AnnotationType == AnnotationType.TestModule)); + item.Annotations.OfType().Any()); } } } \ No newline at end of file diff --git a/Rubberduck.UnitTesting/UnitTesting/TestEngine.cs b/Rubberduck.UnitTesting/UnitTesting/TestEngine.cs index 339cc598e7..83b4d88a4a 100644 --- a/Rubberduck.UnitTesting/UnitTesting/TestEngine.cs +++ b/Rubberduck.UnitTesting/UnitTesting/TestEngine.cs @@ -258,7 +258,7 @@ private void RunWhileSuspended(IEnumerable tests) OnTestStarted(test); // no need to run setup/teardown for ignored tests - if (test.Declaration.Annotations.Any(a => a.AnnotationType == AnnotationType.IgnoreTest)) + if (test.Declaration.Annotations.OfType().Any()) { OnTestCompleted(test, new TestResult(TestOutcome.Ignored)); continue; diff --git a/Rubberduck.UnitTesting/UnitTesting/TestMethod.cs b/Rubberduck.UnitTesting/UnitTesting/TestMethod.cs index 79ca19523a..e886bf5f0d 100644 --- a/Rubberduck.UnitTesting/UnitTesting/TestMethod.cs +++ b/Rubberduck.UnitTesting/UnitTesting/TestMethod.cs @@ -24,8 +24,7 @@ public TestCategory Category { get { - var testMethodAnnotation = (TestMethodAnnotation) Declaration.Annotations - .First(annotation => annotation.AnnotationType == AnnotationType.TestMethod); + var testMethodAnnotation = Declaration.Annotations.OfType().First(); var categorization = testMethodAnnotation.Category.Equals(string.Empty) ? TestExplorer.TestExplorer_Uncategorized : testMethodAnnotation.Category; return new TestCategory(categorization); @@ -37,9 +36,8 @@ public NavigateCodeEventArgs GetNavigationArgs() return new NavigateCodeEventArgs(new QualifiedSelection(Declaration.QualifiedName.QualifiedModuleName, Declaration.Context.GetSelection())); } - public bool IsIgnored => Declaration.Annotations.Any(annotation => annotation.AnnotationType == AnnotationType.IgnoreTest); + public bool IsIgnored => Declaration.Annotations.OfType().Any(); - public bool Equals(TestMethod other) => other != null && Declaration.QualifiedName.Equals(other.Declaration.QualifiedName) && TestCode.Equals(other.TestCode); public override bool Equals(object obj) => obj is TestMethod method && Equals(method); diff --git a/RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs b/RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs index 552bfba8df..d0fc84e9a1 100644 --- a/RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs +++ b/RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs @@ -1,6 +1,9 @@ -using System.Collections.Generic; +using System; +using System.Collections.Generic; +using System.Linq; using NUnit.Framework; using Rubberduck.Parsing.Annotations; +using RubberduckTests.Mocks; namespace RubberduckTests.Annotations { @@ -14,13 +17,13 @@ public void FindMemberAnnotationForRandomAttributeReturnsMemberAttributeAnnotati var attributeName = "VB_Whatever"; var attributeValues = new List{"SomeValue"}; - var expectedAnnotationType = AnnotationType.MemberAttribute; + var expectedAnnotationType = "MemberAttribute"; var expectedValues = new List{"VB_Whatever", "SomeValue"}; - var attributeAnnotationProvider = new AttributeAnnotationProvider(); - var (actualAnnotationType, actualValues) = attributeAnnotationProvider.MemberAttributeAnnotation(attributeName, attributeValues); + var attributeAnnotationProvider = GetAnnotationProvider(); + var (actualAnnotationInfo, actualValues) = attributeAnnotationProvider.MemberAttributeAnnotation(attributeName, attributeValues); - Assert.AreEqual(expectedAnnotationType, actualAnnotationType); + Assert.AreEqual(expectedAnnotationType, actualAnnotationInfo.Name); AssertEqual(expectedValues, actualValues); } @@ -30,52 +33,57 @@ public void FindModuleAnnotationForRandomAttributeReturnsModuleAttributeAnnotati var attributeName = "VB_Whatever"; var attributeValues = new List { "SomeValue" }; - var expectedAnnotationType = AnnotationType.ModuleAttribute; + var expectedAnnotationType = "ModuleAttribute"; var expectedValues = new List { "VB_Whatever", "SomeValue" }; - var attributeAnnotationProvider = new AttributeAnnotationProvider(); - var (actualAnnotationType, actualValues) = attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues); + var attributeAnnotationProvider = GetAnnotationProvider(); + var (annotationInfo, actualValues) = attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues); - Assert.AreEqual(expectedAnnotationType, actualAnnotationType); + Assert.AreEqual(expectedAnnotationType, annotationInfo.Name); AssertEqual(expectedValues, actualValues); } - [TestCase("VB_Description", "\"SomeDescription\"", AnnotationType.ModuleDescription, "\"SomeDescription\"")] - [TestCase("VB_Exposed", "True", AnnotationType.Exposed)] - [TestCase("VB_PredeclaredId", "True", AnnotationType.PredeclaredId)] - public void ModuleAttributeAnnotationReturnsSpecializedAnnotationsWhereApplicable(string attributeName, string annotationValue, AnnotationType expectedAnnotationType, string expectedValue = null) + [TestCase("VB_Description", "\"SomeDescription\"", "ModuleDescription", "\"SomeDescription\"")] + [TestCase("VB_Exposed", "True", "Exposed")] + [TestCase("VB_PredeclaredId", "True", "PredeclaredId")] + public void ModuleAttributeAnnotationReturnsSpecializedAnnotationsWhereApplicable(string attributeName, string annotationValue, string expectedAnnotationType, string expectedValue = null) { var attributeValues = new List { annotationValue }; var expectedValues = expectedValue != null ? new List { expectedValue } : new List(); + + var attributeAnnotationProvider = GetAnnotationProvider(); + var (annotationInfo, actualValues) = attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues); - var attributeAnnotationProvider = new AttributeAnnotationProvider(); - var (actualAnnotationType, actualValues) = attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues); - - Assert.AreEqual(expectedAnnotationType, actualAnnotationType); + Assert.AreEqual(expectedAnnotationType, annotationInfo.Name); AssertEqual(expectedValues, actualValues); } - [TestCase("VB_ProcData.VB_Invoke_Func", "\"A\n14\"", AnnotationType.ExcelHotKey, "\"A\"")] - [TestCase("VB_Description", "\"SomeDescription\"", AnnotationType.Description, "\"SomeDescription\"")] - [TestCase("VB_VarDescription", "\"SomeDescription\"", AnnotationType.VariableDescription, "\"SomeDescription\"")] - [TestCase("VB_UserMemId", "0", AnnotationType.DefaultMember)] - [TestCase("VB_UserMemId", "-4", AnnotationType.Enumerator)] - public void MemberAttributeAnnotationReturnsSpecializedAnnotationsWhereApplicable(string attributeName, string attributeValue, AnnotationType expectedAnnotationType, string expectedValue = null) + [TestCase("VB_ProcData.VB_Invoke_Func", @"A\n14", "ExcelHotkey", "A")] + [TestCase("VB_Description", "\"SomeDescription\"", "Description", "\"SomeDescription\"")] + [TestCase("VB_VarDescription", "\"SomeDescription\"", "VariableDescription", "\"SomeDescription\"")] + [TestCase("VB_UserMemId", "0", "DefaultMember")] + [TestCase("VB_UserMemId", "-4", "Enumerator")] + public void MemberAttributeAnnotationReturnsSpecializedAnnotationsWhereApplicable(string attributeName, string attributeValue, string expectedAnnotationType, string expectedValue = null) { var attributeValues = new List { attributeValue }; var expectedValues = expectedValue != null ? new List { expectedValue } : new List(); - var attributeAnnotationProvider = new AttributeAnnotationProvider(); - var (actualAnnotationType, actualValues) = attributeAnnotationProvider.MemberAttributeAnnotation(attributeName, attributeValues); + var attributeAnnotationProvider = GetAnnotationProvider(); + var (annotationInfo, actualValues) = attributeAnnotationProvider.MemberAttributeAnnotation(attributeName, attributeValues); - Assert.AreEqual(expectedAnnotationType, actualAnnotationType); + Assert.AreEqual(expectedAnnotationType, annotationInfo.Name); AssertEqual(expectedValues, actualValues); } + private AttributeAnnotationProvider GetAnnotationProvider() + { + return new AttributeAnnotationProvider(MockParser.GetWellKnownAnnotationTypes().Where(annot => typeof(IAttributeAnnotation).IsAssignableFrom(annot))); + } + private static void AssertEqual(IReadOnlyList expectedList, IReadOnlyList actualList) { Assert.AreEqual(expectedList.Count, actualList.Count); diff --git a/RubberduckTests/Commands/UnitTestCommandTests.cs b/RubberduckTests/Commands/UnitTestCommandTests.cs index 334fc41ca0..6500d25958 100644 --- a/RubberduckTests/Commands/UnitTestCommandTests.cs +++ b/RubberduckTests/Commands/UnitTestCommandTests.cs @@ -321,7 +321,7 @@ End Property var testModule = state.DeclarationFinder.FindStdModule($"{TestModuleBaseName}1", project); - Assert.IsTrue(testModule.Annotations.Any(a => a.AnnotationType == AnnotationType.TestModule)); + Assert.IsTrue(testModule.Annotations.Any(a => a is TestModuleAnnotation)); var stubIdentifierNames = new List { @@ -375,7 +375,7 @@ End Property var testModule = state.DeclarationFinder.FindStdModule($"{TestModuleBaseName}1", project); - Assert.IsTrue(testModule.Annotations.Any(a => a.AnnotationType == AnnotationType.TestModule)); + Assert.IsTrue(testModule.Annotations.Any(a => a is TestModuleAnnotation)); var stubs = state.DeclarationFinder.AllUserDeclarations.Where(d => d.IdentifierName.EndsWith(TestMethodBaseName)).ToList(); Assert.AreEqual(0, stubs.Count); @@ -419,7 +419,7 @@ End Enum var testModule = state.DeclarationFinder.FindStdModule($"{TestModuleBaseName}1", project); - Assert.IsTrue(testModule.Annotations.Any(a => a.AnnotationType == AnnotationType.TestModule)); + Assert.IsTrue(testModule.Annotations.Any(a => a is TestModuleAnnotation)); var stubs = state.DeclarationFinder.AllUserDeclarations.Where(d => d.IdentifierName.EndsWith(TestMethodBaseName)).ToList(); Assert.AreEqual(0, stubs.Count); diff --git a/RubberduckTests/Grammar/AnnotationTests.cs b/RubberduckTests/Grammar/AnnotationTests.cs index 2b3b100257..5810cf9835 100644 --- a/RubberduckTests/Grammar/AnnotationTests.cs +++ b/RubberduckTests/Grammar/AnnotationTests.cs @@ -1,235 +1,52 @@ using NUnit.Framework; using Rubberduck.Parsing.Annotations; using Rubberduck.VBEditor; +using System; +using System.Collections.Generic; namespace RubberduckTests.Grammar { [TestFixture] + [Category("Grammar")] + [Category("Annotations")] public class AnnotationTests { - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void NotRecognizedAnnotation_TypeIsNotRecognized() - { - var annotation = new NotRecognizedAnnotation(new QualifiedSelection(), null, null); - Assert.AreEqual(AnnotationType.NotRecognized, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void TestModuleAnnotation_TypeIsTestModule() - { - var annotation = new TestModuleAnnotation(new QualifiedSelection(), null, null); - Assert.AreEqual(AnnotationType.TestModule, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void ModuleInitializeAnnotation_TypeIsModuleInitialize() - { - var annotation = new ModuleInitializeAnnotation(new QualifiedSelection(), null, null); - Assert.AreEqual(AnnotationType.ModuleInitialize, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void ModuleCleanupAnnotation_TypeIsModuleCleanup() - { - var annotation = new ModuleCleanupAnnotation(new QualifiedSelection(), null, null); - Assert.AreEqual(AnnotationType.ModuleCleanup, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void TestMethodAnnotation_TypeIsTestTest() - { - var annotation = new TestMethodAnnotation(new QualifiedSelection(), null, new[] { "param" }); - Assert.AreEqual(AnnotationType.TestMethod, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void TestInitializeAnnotation_TypeIsTestInitialize() - { - var annotation = new TestInitializeAnnotation(new QualifiedSelection(), null, null); - Assert.AreEqual(AnnotationType.TestInitialize, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void TestCleanupAnnotation_TypeIsTestCleanup() - { - var annotation = new TestCleanupAnnotation(new QualifiedSelection(), null, null); - Assert.AreEqual(AnnotationType.TestCleanup, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void IgnoreTestAnnotation_TypeIsIgnoreTest() - { - var annotation = new IgnoreTestAnnotation(new QualifiedSelection(), null, null); - Assert.AreEqual(AnnotationType.IgnoreTest, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void IgnoreAnnotation_TypeIsIgnore() - { - var annotation = new IgnoreAnnotation(new QualifiedSelection(), null, null); - Assert.AreEqual(AnnotationType.Ignore, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void FolderAnnotation_TypeIsFolder() - { - var annotation = new FolderAnnotation(new QualifiedSelection(), null, new[] { "param" }); - Assert.AreEqual(AnnotationType.Folder, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void NoIndentAnnotation_TypeIsNoIndent() - { - var annotation = new NoIndentAnnotation(new QualifiedSelection(), null, null); - Assert.AreEqual(AnnotationType.NoIndent, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void InterfaceAnnotation_TypeIsInterface() - { - var annotation = new InterfaceAnnotation(new QualifiedSelection(), null, null); - Assert.AreEqual(AnnotationType.Interface, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void ModuleAttributeAnnotation_TypeIsModuleAttribute() - { - var annotation = new ModuleAttributeAnnotation(new QualifiedSelection(), null, new[] { "Attribute", "Value" }); - Assert.AreEqual(AnnotationType.ModuleAttribute, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void MemberAttributeAnnotation_TypeIsMemberAttribute() - { - var annotation = new MemberAttributeAnnotation(new QualifiedSelection(), null, new[] { "Attribute", "Value" }); - Assert.AreEqual(AnnotationType.MemberAttribute, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void DescriptionAnnotation_TypeIsDescription() - { - var annotation = new DescriptionAnnotation(new QualifiedSelection(), null, new[] { "Desc"}); - Assert.AreEqual(AnnotationType.Description, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void ModuleDescriptionAnnotation_TypeIsModuleDescription() - { - var annotation = new ModuleDescriptionAnnotation(new QualifiedSelection(), null, new[] { "Desc" }); - Assert.AreEqual(AnnotationType.ModuleDescription, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void VariableDescriptionAnnotation_TypeIsModuleDescription() - { - var annotation = new VariableDescriptionAnnotation(new QualifiedSelection(), null, new[] { "Desc" }); - Assert.AreEqual(AnnotationType.VariableDescription, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void DefaultMemberAnnotation_TypeIsDefaultMember() - { - var annotation = new DefaultMemberAnnotation(new QualifiedSelection(), null, new[] { "param" }); - Assert.AreEqual(AnnotationType.DefaultMember, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void EnumerationMemberAnnotation_TypeIsEnumerator() - { - var annotation = new EnumeratorMemberAnnotation(new QualifiedSelection(), null, new[] { "param" }); - Assert.AreEqual(AnnotationType.Enumerator, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void ExposedModuleAnnotation_TypeIsExposed() - { - var annotation = new ExposedModuleAnnotation(new QualifiedSelection(), null, null); - Assert.AreEqual(AnnotationType.Exposed, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void IgnoreModuleAnnotation_TypeIsIgnoreModule() - { - var annotation = new IgnoreModuleAnnotation(new QualifiedSelection(), null, null); - Assert.AreEqual(AnnotationType.IgnoreModule, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void PredeclaredIdAnnotation_TypeIsPredeclaredId() - { - var annotation = new PredeclaredIdAnnotation(new QualifiedSelection(), null, null); - Assert.AreEqual(AnnotationType.PredeclaredId, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void ObsoleteAnnotation_TypeIsObsolete() - { - var annotation = new ObsoleteAnnotation(new QualifiedSelection(), null, new[] { "param" }); - Assert.AreEqual(AnnotationType.Obsolete, annotation.AnnotationType); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void IgnoreAnnotation_CanBeAppliedMultipleTimes() - { - var annotation = new IgnoreAnnotation(new QualifiedSelection(), null, null); - Assert.True(annotation.AllowMultiple); - } - - [Category("Grammar")] - [Category("Annotations")] - [Test] - public void IgnoreModuleAnnotation_CanBeAppliedMultipleTimes() - { - var annotation = new IgnoreModuleAnnotation(new QualifiedSelection(), null, null); - Assert.True(annotation.AllowMultiple); + [TestCase(typeof(DefaultMemberAnnotation), "DefaultMember", new[] { "param" })] + [TestCase(typeof(DescriptionAnnotation), "Description", new[] { "desc" })] + [TestCase(typeof(EnumeratorMemberAnnotation), "Enumerator", new[] { "param" })] + [TestCase(typeof(ExcelHotKeyAnnotation), "ExcelHotkey", new [] { "A" })] + [TestCase(typeof(ExposedModuleAnnotation), "Exposed")] + [TestCase(typeof(FolderAnnotation), "Folder", new[] { "param" })] + [TestCase(typeof(IgnoreAnnotation), "Ignore")] + [TestCase(typeof(IgnoreModuleAnnotation), "IgnoreModule")] + [TestCase(typeof(IgnoreTestAnnotation), "IgnoreTest")] + [TestCase(typeof(InterfaceAnnotation), "Interface")] + [TestCase(typeof(MemberAttributeAnnotation), "MemberAttribute", new[] { "Attribute", "Value" })] + [TestCase(typeof(ModuleAttributeAnnotation), "ModuleAttribute", new[] { "Attribute", "Value" })] + [TestCase(typeof(ModuleCleanupAnnotation), "ModuleCleanup")] + [TestCase(typeof(ModuleDescriptionAnnotation), "ModuleDescription", new[] { "desc" })] + [TestCase(typeof(ModuleInitializeAnnotation), "ModuleInitialize")] + [TestCase(typeof(NoIndentAnnotation), "NoIndent")] + [TestCase(typeof(NotRecognizedAnnotation), "NotRecognized")] + [TestCase(typeof(ObsoleteAnnotation), "Obsolete", new [] { "justification" })] + [TestCase(typeof(PredeclaredIdAnnotation), "PredeclaredId")] + [TestCase(typeof(TestCleanupAnnotation), "TestCleanup")] + [TestCase(typeof(TestInitializeAnnotation), "TestInitialize")] + [TestCase(typeof(TestMethodAnnotation), "TestMethod")] + [TestCase(typeof(TestModuleAnnotation), "TestModule")] + [TestCase(typeof(VariableDescriptionAnnotation), "VariableDescription", new[] { "desc" })] + public void AnnotationTypes_MatchExpectedAnnotationNames(Type annotationType, string name, IEnumerable args = null) + { + var annotation = (IAnnotation) Activator.CreateInstance(annotationType, new QualifiedSelection(), null, args ?? new List()); + Assert.AreEqual(name, annotation.AnnotationType); + } + + [TestCase(typeof(IgnoreAnnotation))] + [TestCase(typeof(IgnoreModuleAnnotation))] + public void AnnotationTypes_MultipleApplicationsAllowed(Type annotationType) + { + var annotation = (IAnnotation)Activator.CreateInstance(annotationType, new QualifiedSelection(), null, null); + Assert.IsTrue(annotation.MetaInformation.AllowMultiple); } } } \ No newline at end of file diff --git a/RubberduckTests/Grammar/ResolverTests.cs b/RubberduckTests/Grammar/ResolverTests.cs index 7274f7852b..85e4c8e3b7 100644 --- a/RubberduckTests/Grammar/ResolverTests.cs +++ b/RubberduckTests/Grammar/ResolverTests.cs @@ -1389,10 +1389,9 @@ End Sub item.DeclarationType == DeclarationType.Variable && !item.IsUndeclared); var usage = declaration.References.Single(); - var annotation = (IgnoreAnnotation)usage.Annotations.First(); + var annotation = (IgnoreAnnotation) usage.Annotations.First(); Assert.IsTrue( usage.Annotations.Count() == 1 - && annotation.AnnotationType == AnnotationType.Ignore && annotation.InspectionNames.Count() == 1 && annotation.InspectionNames.First() == "UnassignedVariableUsage"); } @@ -1423,9 +1422,7 @@ End Sub var annotation2 = (IgnoreAnnotation)usage.Annotations.ElementAt(1); Assert.AreEqual(2, usage.Annotations.Count()); - Assert.AreEqual(AnnotationType.Ignore, annotation1.AnnotationType); - Assert.AreEqual(AnnotationType.Ignore, annotation2.AnnotationType); - + Assert.IsTrue(usage.Annotations.Any(a => ((IgnoreAnnotation)a).InspectionNames.First() == "UseMeaningfulName")); Assert.IsTrue(usage.Annotations.Any(a => ((IgnoreAnnotation)a).InspectionNames.First() == "UnassignedVariableUsage")); } @@ -1447,9 +1444,9 @@ public void AnnotatedDeclaration_LinesAbove_HaveAnnotations() { var declaration = state.AllUserDeclarations.First(f => f.DeclarationType == DeclarationType.Procedure); - Assert.IsTrue(declaration.Annotations.Count() == 2); - Assert.IsTrue(declaration.Annotations.Any(a => a.AnnotationType == AnnotationType.TestMethod)); - Assert.IsTrue(declaration.Annotations.Any(a => a.AnnotationType == AnnotationType.IgnoreTest)); + Assert.AreEqual(2, declaration.Annotations.Count(), "Annotation count mismatch"); + Assert.IsTrue(declaration.Annotations.Any(a => a is TestMethodAnnotation)); + Assert.IsTrue(declaration.Annotations.Any(a => a is IgnoreTestAnnotation)); } } @@ -2882,7 +2879,7 @@ End Sub var declaration = state.AllUserDeclarations.Single(item => item.IdentifierName == "orgs"); - var annotation = declaration.Annotations.SingleOrDefault(item => item.AnnotationType == AnnotationType.Ignore); + var annotation = declaration.Annotations.SingleOrDefault(item => item is IgnoreAnnotation); Assert.IsNotNull(annotation); Assert.IsTrue(results.SequenceEqual(((IgnoreAnnotation)annotation).InspectionNames)); } @@ -2908,7 +2905,7 @@ End Sub var declaration = state.AllUserDeclarations.Single(item => item.IdentifierName == "orgs"); - var annotation = declaration.Annotations.SingleOrDefault(item => item.AnnotationType == AnnotationType.Ignore); + var annotation = declaration.Annotations.SingleOrDefault(item => item is IgnoreAnnotation); Assert.IsNotNull(annotation); Assert.IsTrue(results.SequenceEqual(((IgnoreAnnotation)annotation).InspectionNames)); } diff --git a/RubberduckTests/Inspections/AttributeValueOutOfSyncInspectionTests.cs b/RubberduckTests/Inspections/AttributeValueOutOfSyncInspectionTests.cs index eb94b32b0f..4f1b924b47 100644 --- a/RubberduckTests/Inspections/AttributeValueOutOfSyncInspectionTests.cs +++ b/RubberduckTests/Inspections/AttributeValueOutOfSyncInspectionTests.cs @@ -218,7 +218,7 @@ public void ResultContainsAnnotationAndAttributeValues() var inspectionResults = InspectionResults(inputCode); var inspectionResult = inspectionResults.First(); - Assert.AreEqual(AnnotationType.MemberAttribute, inspectionResult.Properties.Annotation.AnnotationType); + Assert.IsInstanceOf(inspectionResult.Properties.Annotation); Assert.AreEqual("VB_UserMemId", inspectionResult.Properties.Annotation.Attribute); Assert.AreEqual("-4", inspectionResult.Properties.Annotation.AttributeValues[0]); Assert.AreEqual("40", inspectionResult.Properties.AttributeValues[0]); diff --git a/RubberduckTests/Mocks/MockParser.cs b/RubberduckTests/Mocks/MockParser.cs index 44372da87e..0a4cba4738 100644 --- a/RubberduckTests/Mocks/MockParser.cs +++ b/RubberduckTests/Mocks/MockParser.cs @@ -25,6 +25,7 @@ using Rubberduck.VBEditor.SafeComWrappers.Abstract; using Rubberduck.VBEditor.SourceCodeHandling; using Rubberduck.VBEditor.Utility; +using Rubberduck.Parsing.Annotations; namespace RubberduckTests.Mocks { @@ -75,6 +76,7 @@ public static (SynchronousParseCoordinator parser, IRewritingManager rewritingMa var mainTokenStreamParser = new VBATokenStreamParser(mainParseErrorListenerFactory, mainParseErrorListenerFactory); var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider(); var stringParser = new TokenStreamParserStringParserAdapterWithPreprocessing(tokenStreamProvider, mainTokenStreamParser, preprocessor); + var vbaParserAnnotationFactory = new VBAParserAnnotationFactory(GetWellKnownAnnotationTypes()); var projectManager = new RepositoryProjectManager(projectRepository); var moduleToModuleReferenceManager = new ModuleToModuleReferenceManager(); var supertypeClearer = new SynchronousSupertypeClearer(state); @@ -106,7 +108,8 @@ public static (SynchronousParseCoordinator parser, IRewritingManager rewritingMa var moduleParser = new ModuleParser( codePaneSourceCodeHandler, attributesSourceCodeHandler, - stringParser); + stringParser, + vbaParserAnnotationFactory); var parseRunner = new SynchronousParseRunner( state, parserStateManager, @@ -159,6 +162,14 @@ public static (SynchronousParseCoordinator parser, IRewritingManager rewritingMa return (parser, rewritingManager); } + public static IEnumerable GetWellKnownAnnotationTypes() + { + return Assembly.GetAssembly(typeof(IAnnotation)) + .GetTypes() + .Where(candidate => typeof(IAnnotation).IsAssignableFrom(candidate) + && !candidate.IsAbstract); + } + public static SynchronousParseCoordinator Create(IVBE vbe, RubberduckParserState state, IProjectsRepository projectRepository, string serializedComProjectsPath = null) { return CreateWithRewriteManager(vbe, state, projectRepository, serializedComProjectsPath).parser; diff --git a/RubberduckTests/PostProcessing/AnnotationUpdaterTests.cs b/RubberduckTests/PostProcessing/AnnotationUpdaterTests.cs index bdad3e83bc..22d8983065 100644 --- a/RubberduckTests/PostProcessing/AnnotationUpdaterTests.cs +++ b/RubberduckTests/PostProcessing/AnnotationUpdaterTests.cs @@ -42,7 +42,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = AnnotationType.MemberAttribute; + var annotationToAdd = new AnnotationAttribute("MemberAttribute", AnnotationTarget.Member); var annotationValues = new List { "VB_Ext_Key", "\"Key\"", "\"Value\"" }; string actualCode; @@ -96,7 +96,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = AnnotationType.ModuleAttribute; + var annotationToAdd = new AnnotationAttribute("ModuleAttribute", AnnotationTarget.Module); var annotationValues = new List { "VB_Ext_Key", "\"Key\"", "\"Value\"" }; string actualCode; @@ -143,7 +143,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = AnnotationType.ModuleAttribute; + var annotationToAdd = new AnnotationAttribute("ModuleAttribute", AnnotationTarget.Module); var annotationValues = new List { "VB_Ext_Key", "\"Key\"", "\"Value\"" }; string actualCode; @@ -196,7 +196,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = AnnotationType.MemberAttribute; + var annotationToAdd = new AnnotationAttribute("MemberAttribute", AnnotationTarget.Member); var annotationValues = new List { "VB_Ext_Key", "\"Key\"", "\"Value\"" }; string actualCode; @@ -254,7 +254,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = AnnotationType.Ignore; + var annotationToAdd = new AnnotationAttribute("Ignore", AnnotationTarget.General); var annotationValues = new List { "ObsoleteMemberUsage" }; string actualCode; @@ -301,7 +301,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = AnnotationType.Obsolete; + var annotationToAdd = new AnnotationAttribute("Obsolete", AnnotationTarget.Member | AnnotationTarget.Variable); string actualCode; var (component, rewriteSession, state) = TestSetup(inputCode); @@ -347,7 +347,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = AnnotationType.Obsolete; + var annotationToAdd = new AnnotationAttribute("Obsolete", AnnotationTarget.Member | AnnotationTarget.Variable); string actualCode; var (component, rewriteSession, state) = TestSetup(inputCode); @@ -674,7 +674,7 @@ Option Explicit var moduleDeclaration = state.DeclarationFinder .UserDeclarations(DeclarationType.ProceduralModule) .First(); - var annotationsToRemove = moduleDeclaration.Annotations.Where(annotation => annotation.AnnotationType != AnnotationType.Exposed); + var annotationsToRemove = moduleDeclaration.Annotations.Where(annotation => !(annotation is ExposedModuleAnnotation)); var annotationUpdater = new AnnotationUpdater(); annotationUpdater.RemoveAnnotations(rewriteSession, annotationsToRemove); @@ -718,7 +718,7 @@ End Sub bar = vbNullString End Sub "; - var newAnnotation = AnnotationType.MemberAttribute; + var newAnnotation = new AnnotationAttribute("MemberAttribute", AnnotationTarget.Member); var newAnnotationValues = new List { "VB_ExtKey", "\"Key\"", "\"Value\"" }; string actualCode; @@ -728,7 +728,7 @@ End Sub var fooDeclaration = state.DeclarationFinder .UserDeclarations(DeclarationType.Procedure) .First(decl => decl.IdentifierName == "Foo"); - var annotationToUpdate = fooDeclaration.Annotations.First(annotation => annotation.AnnotationType == AnnotationType.Description); + var annotationToUpdate = fooDeclaration.Annotations.First(annotation => annotation is DescriptionAnnotation); var annotationUpdater = new AnnotationUpdater(); annotationUpdater.UpdateAnnotation(rewriteSession, annotationToUpdate, newAnnotation, newAnnotationValues); diff --git a/RubberduckTests/QuickFixes/AddAttributeAnnotationQuickFixTests.cs b/RubberduckTests/QuickFixes/AddAttributeAnnotationQuickFixTests.cs index 96e1325336..73f24b6e3b 100644 --- a/RubberduckTests/QuickFixes/AddAttributeAnnotationQuickFixTests.cs +++ b/RubberduckTests/QuickFixes/AddAttributeAnnotationQuickFixTests.cs @@ -4,6 +4,9 @@ using Rubberduck.Parsing.Annotations; using Rubberduck.Parsing.Inspections.Abstract; using Rubberduck.Parsing.VBA; +using RubberduckTests.Mocks; +using System; +using System.Linq; namespace RubberduckTests.QuickFixes { @@ -153,7 +156,9 @@ public void KnownMemberAttributeWithoutAnnotationWhileOtherAttributeWithAnnotati protected override IQuickFix QuickFix(RubberduckParserState state) { - return new AddAttributeAnnotationQuickFix(new AnnotationUpdater(), new AttributeAnnotationProvider()); + // FIXME actually inject the annotations here... + return new AddAttributeAnnotationQuickFix(new AnnotationUpdater(), + new AttributeAnnotationProvider(MockParser.GetWellKnownAnnotationTypes().Where(annotation => typeof(IAttributeAnnotation).IsAssignableFrom(annotation)))); } } } \ No newline at end of file diff --git a/RubberduckTests/QuickFixes/AdjustAttributeAnnotationQuickFixTests.cs b/RubberduckTests/QuickFixes/AdjustAttributeAnnotationQuickFixTests.cs index f801278784..b75b4cfa0f 100644 --- a/RubberduckTests/QuickFixes/AdjustAttributeAnnotationQuickFixTests.cs +++ b/RubberduckTests/QuickFixes/AdjustAttributeAnnotationQuickFixTests.cs @@ -7,6 +7,8 @@ using Rubberduck.VBEditor.SafeComWrappers; using Rubberduck.VBEditor.SafeComWrappers.Abstract; using RubberduckTests.Mocks; +using System; +using System.Linq; namespace RubberduckTests.QuickFixes { @@ -107,7 +109,8 @@ protected override IVBE TestVbe(string code, out IVBComponent component) protected override IQuickFix QuickFix(RubberduckParserState state) { - return new AdjustAttributeAnnotationQuickFix(new AnnotationUpdater(), new AttributeAnnotationProvider()); + return new AdjustAttributeAnnotationQuickFix(new AnnotationUpdater(), + new AttributeAnnotationProvider(MockParser.GetWellKnownAnnotationTypes().Where(annotation => typeof(IAttributeAnnotation).IsAssignableFrom(annotation)))); } } } \ No newline at end of file diff --git a/RubberduckTests/QuickFixes/RemoveDuplicatedAnnotationQuickFixTests.cs b/RubberduckTests/QuickFixes/RemoveDuplicatedAnnotationQuickFixTests.cs index 5e6d78f482..36ec8cdb29 100644 --- a/RubberduckTests/QuickFixes/RemoveDuplicatedAnnotationQuickFixTests.cs +++ b/RubberduckTests/QuickFixes/RemoveDuplicatedAnnotationQuickFixTests.cs @@ -182,7 +182,7 @@ public void RemoveDuplicatedAnnotation_QuickFixWorks_RemoveDuplicatesOfOnlyOneAn '@TestMethod Public Sub Foo End Sub"; - Func conditionToFix = result => result.Properties.AnnotationType == AnnotationType.Obsolete; + Func conditionToFix = result => result.Properties.AnnotationType == typeof(ObsoleteAnnotation); var actualCode = ApplyQuickFixToFirstInspectionResultSatisfyingPredicate(inputCode, state => new DuplicatedAnnotationInspection(state), conditionToFix); Assert.AreEqual(expectedCode, actualCode); } From 5ac876eb9579288b931bdc50d4c5aa4a17ea66d7 Mon Sep 17 00:00:00 2001 From: Vogel612 Date: Fri, 30 Aug 2019 23:32:27 +0200 Subject: [PATCH 2/4] Second redesign for annotations This moves static information on annotations into implementations of IAnnotation and introduces a ParseTreeAnnotation class to correlate parser contexts to annotations. With that change we get a clearer separation between the annotation and it's use. For workability, a handful of extension methods have been added, some have been adapted. Additionally a large number of predicates and filterings have been adjusted to the new API. --- Rubberduck.API/VBA/Parser.cs | 4 +- .../AttributeValueOutOfSyncInspection.cs | 28 +++-- .../DuplicatedAnnotationInspection.cs | 4 +- .../Concrete/IllegalAnnotationInspection.cs | 8 +- .../Concrete/MissingAttributeInspection.cs | 19 ++-- .../MissingMemberAnnotationInspection.cs | 11 +- .../MissingModuleAnnotationInspection.cs | 9 +- .../Concrete/ModuleWithoutFolderInspection.cs | 2 +- .../Concrete/ObsoleteMemberUsageInspection.cs | 6 +- .../Extensions/IgnoreRelatedExtensions.cs | 15 +-- .../QuickFixes/AddMissingAttributeQuickFix.cs | 10 +- .../AdjustAttributeAnnotationQuickFix.cs | 2 +- .../AdjustAttributeValuesQuickFix.cs | 10 +- .../QuickFixes/IgnoreOnceQuickFix.cs | 12 +- .../RemoveDuplicatedAnnotationQuickFix.cs | 4 +- .../UI/CodeExplorer/Commands/IndentCommand.cs | 10 +- .../ComCommands/AddTestMethodCommand.cs | 2 +- .../AddTestMethodExpectedErrorCommand.cs | 2 +- .../UI/UnitTesting/TestExplorerViewModel.cs | 4 +- .../Root/RubberduckIoCInstaller.cs | 5 +- .../Annotations/AnnotationBase.cs | 46 ++------ .../Annotations/AnnotationListener.cs | 6 +- .../AttributeAnnotationExtensions.cs | 30 +++++ .../AttributeAnnotationProvider.cs | 107 ++++-------------- Rubberduck.Parsing/Annotations/IAnnotation.cs | 24 +--- .../Annotations/IAnnotationFactory.cs | 2 +- .../Annotations/IAttributeAnnotation.cs | 46 +------- .../IAttributeAnnotationProvider.cs | 4 +- .../DefaultMemberAnnotation.cs | 10 +- .../Implementations/DescriptionAnnotation.cs | 6 +- .../DescriptionAttributeAnnotationBase.cs | 15 +-- .../EnumeratorMemberAnnotation.cs | 6 +- .../Implementations/ExcelHotKeyAnnotation.cs | 21 ++-- .../ExposedModuleAnnotation.cs | 6 +- .../FixedAttributeValueAnnotationBase.cs | 39 ++++--- .../FlexibleAttributeAnnotationBase.cs | 32 +++++- .../FlexibleAttributeValueAnnotationBase.cs | 37 +++--- .../Implementations/FolderAnnotation.cs | 16 +-- .../Implementations/IgnoreAnnotation.cs | 24 +--- .../Implementations/IgnoreModuleAnnotation.cs | 21 +--- .../Implementations/IgnoreTestAnnotation.cs | 8 +- .../Implementations/InterfaceAnnotation.cs | 8 +- .../MemberAttributeAnnotation.cs | 7 +- .../ModuleAttributeAnnotation.cs | 6 +- .../ModuleCleanupAnnotation.cs | 11 +- .../ModuleDescriptionAnnotation.cs | 6 +- .../ModuleInitializeAnnotation.cs | 11 +- .../Implementations/NoIndentAnnotation.cs | 8 +- .../NotRecognizedAnnotation.cs | 10 +- .../Implementations/ObsoleteAnnotation.cs | 11 +- .../PredeclaredIdAnnotation.cs | 6 +- .../Implementations/TestCleanupAnnotation.cs | 8 +- .../TestInitializeAnnotation.cs | 11 +- .../Implementations/TestMethodAnnotation.cs | 26 ++--- .../Implementations/TestModuleAnnotation.cs | 12 +- .../VariableDescriptionAnnotation.cs | 8 +- .../InvalidAnnotationArgumentException.cs | 3 +- .../Annotations/ParseTreeAnnotation.cs | 81 +++++++++++++ .../Annotations/VBAParserAnnotationFactory.cs | 44 +++---- Rubberduck.Parsing/Symbols/Attributes.cs | 16 +-- .../Symbols/ClassModuleDeclaration.cs | 6 +- Rubberduck.Parsing/Symbols/Declaration.cs | 12 +- .../DeclarationLoaders/AliasDeclarations.cs | 58 +++++----- .../DeclarationLoaders/DebugDeclarations.cs | 10 +- .../FormEventDeclarations.cs | 12 +- .../SpecialFormDeclarations.cs | 4 +- .../Symbols/DocumentModuleDeclaration.cs | 2 +- .../Symbols/EventDeclaration.cs | 2 +- .../Symbols/ExternalProcedureDeclaration.cs | 2 +- .../Symbols/FunctionDeclaration.cs | 2 +- .../Symbols/IDeclarationFinderFactory.cs | 2 +- .../Symbols/IdentifierReference.cs | 6 +- .../Symbols/ModuleBodyElementDeclaration.cs | 2 +- .../Symbols/ModuleDeclaration.cs | 10 +- .../Symbols/ProceduralModuleDeclaration.cs | 8 +- .../Symbols/PropertyDeclaration.cs | 2 +- .../Symbols/PropertyGetDeclaration.cs | 2 +- .../Symbols/PropertyLetDeclaration.cs | 2 +- .../Symbols/PropertySetDeclaration.cs | 2 +- .../Symbols/SubroutineDeclaration.cs | 2 +- .../Symbols/UnboundMemberDeclaration.cs | 2 +- .../Symbols/ValuedDeclaration.cs | 2 +- .../Symbols/VariableDeclaration.cs | 2 +- Rubberduck.Parsing/VBA/AnnotationUpdater.cs | 32 +++--- ...oncurrentlyConstructedDeclarationFinder.cs | 4 +- ...ntlyConstructedDeclarationFinderFactory.cs | 2 +- .../DeclarationCaching/DeclarationFinder.cs | 27 +++-- .../DeclarationFinderFactory.cs | 2 +- .../DeclarationResolveRunnerBase.cs | 8 +- .../DeclarationSymbolsListener.cs | 16 +-- Rubberduck.Parsing/VBA/IAnnotationUpdater.cs | 12 +- Rubberduck.Parsing/VBA/ModuleState.cs | 10 +- .../VBA/Parsing/IModuleParser.cs | 4 +- .../VBA/Parsing/ModuleParser.cs | 2 +- .../BoundExpressionVisitor.cs | 2 +- .../IdentifierReferenceResolver.cs | 4 +- .../VBA/RubberduckParserState.cs | 12 +- .../UnitTesting/TestDiscovery.cs | 14 +-- .../UnitTesting/TestMethod.cs | 8 +- .../Annotations/AnnotationResolutionTests.cs | 12 +- .../AttributeAnnotationProviderTests.cs | 10 +- .../CodeExplorerComponentViewModelTests.cs | 2 +- .../CodeExplorer/CodeExplorerFolderTests.cs | 21 ++-- .../Commands/UnitTestCommandTests.cs | 8 +- RubberduckTests/Grammar/AnnotationTests.cs | 30 ++--- RubberduckTests/Grammar/ResolverTests.cs | 31 ++--- .../AttributeValueOutOfSyncInspectionTests.cs | 7 +- .../Inspections/InspectionResultTests.cs | 4 +- .../UntypedFunctionUsageInspectionTests.cs | 62 +++++----- RubberduckTests/Mocks/MockParser.cs | 7 +- .../PostProcessing/AnnotationUpdaterTests.cs | 20 ++-- .../AddAttributeAnnotationQuickFixTests.cs | 10 +- .../AdjustAttributeAnnotationQuickFixTests.cs | 2 +- ...RemoveDuplicatedAnnotationQuickFixTests.cs | 2 +- .../Refactoring/Rename/RenameTests.cs | 24 ++-- .../Symbols/DeclarationFinderTests.cs | 2 +- 116 files changed, 711 insertions(+), 822 deletions(-) create mode 100644 Rubberduck.Parsing/Annotations/AttributeAnnotationExtensions.cs create mode 100644 Rubberduck.Parsing/Annotations/ParseTreeAnnotation.cs diff --git a/Rubberduck.API/VBA/Parser.cs b/Rubberduck.API/VBA/Parser.cs index 10c3882b0d..593836bece 100644 --- a/Rubberduck.API/VBA/Parser.cs +++ b/Rubberduck.API/VBA/Parser.cs @@ -107,8 +107,8 @@ internal Parser(object vbe) : this() var preprocessorErrorListenerFactory = new PreprocessingParseErrorListenerFactory(); var preprocessorParser = new VBAPreprocessorParser(preprocessorErrorListenerFactory, preprocessorErrorListenerFactory); var preprocessor = new VBAPreprocessor(preprocessorParser, compilationsArgumentsCache); - // FIXME inject annotation types to allow Rubberduck api users to access Annotations from VBA code - var annotationProcessor = new VBAParserAnnotationFactory(new List()); + // FIXME inject annotations to allow Rubberduck api users to access Annotations from VBA code + var annotationProcessor = new VBAParserAnnotationFactory(new List()); var mainParseErrorListenerFactory = new MainParseErrorListenerFactory(); var mainTokenStreamParser = new VBATokenStreamParser(mainParseErrorListenerFactory, mainParseErrorListenerFactory); var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider(); diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs index a672a6c140..7e46b8f99e 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs @@ -49,23 +49,26 @@ public AttributeValueOutOfSyncInspection(RubberduckParserState state) protected override IEnumerable DoGetInspectionResults() { var declarationsWithAttributeAnnotations = State.DeclarationFinder.AllUserDeclarations - .Where(declaration => declaration.Annotations.Any(annotation => annotation is IAttributeAnnotation)); + .Where(declaration => declaration.Annotations.Any(pta => pta.Annotation is IAttributeAnnotation)); var results = new List(); foreach (var declaration in declarationsWithAttributeAnnotations.Where(decl => decl.QualifiedModuleName.ComponentType != ComponentType.Document)) { - foreach (var annotation in declaration.Annotations.OfType()) + foreach (var annotationInstance in declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation)) { - if (HasDifferingAttributeValues(declaration, annotation, out var attributeValues)) + var annotation = annotationInstance.Annotation; + if (HasDifferingAttributeValues(declaration, annotationInstance, out var attributeValues)) { + var attributeName = annotationInstance.Attribute(); + var description = string.Format(InspectionResults.AttributeValueOutOfSyncInspection, - annotation.Attribute, + attributeName, string.Join(", ", attributeValues), - annotation.AnnotationType); + annotation.Name); var result = new DeclarationInspectionResult(this, description, declaration, - new QualifiedContext(declaration.QualifiedModuleName, annotation.Context)); - result.Properties.Annotation = annotation; - result.Properties.AttributeName = annotation.Attribute; + new QualifiedContext(declaration.QualifiedModuleName, annotationInstance.Context)); + result.Properties.Annotation = annotationInstance; + result.Properties.AttributeName = attributeName; result.Properties.AttributeValues = attributeValues; results.Add(result); @@ -76,16 +79,17 @@ protected override IEnumerable DoGetInspectionResults() return results; } - private static bool HasDifferingAttributeValues(Declaration declaration, IAttributeAnnotation annotation, out IReadOnlyList attributeValues) + private static bool HasDifferingAttributeValues(Declaration declaration, ParseTreeAnnotation annotationInstance, out IReadOnlyList attributeValues) { + var attribute = annotationInstance.Attribute(); var attributeNodes = declaration.DeclarationType.HasFlag(DeclarationType.Module) - ? declaration.Attributes.AttributeNodesFor(annotation) - : declaration.Attributes.AttributeNodesFor(annotation, declaration.IdentifierName); + ? declaration.Attributes.AttributeNodesFor(annotationInstance) + : declaration.Attributes.AttributeNodesFor(annotationInstance, declaration.IdentifierName); foreach (var attributeNode in attributeNodes) { var values = attributeNode.Values; - if (!annotation.AttributeValues.SequenceEqual(values)) + if (!annotationInstance.AttributeValues().SequenceEqual(values)) { attributeValues = values; return true; diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs index 2899a925d4..fe4ffeb47d 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs @@ -46,8 +46,8 @@ protected override IEnumerable DoGetInspectionResults() foreach (var declaration in State.AllUserDeclarations) { var duplicateAnnotations = declaration.Annotations - .GroupBy(annotation => annotation.GetType()) - .Where(group => !group.First().MetaInformation.AllowMultiple && group.Count() > 1); + .GroupBy(pta => pta.Annotation) + .Where(group => !group.First().Annotation.AllowMultiple && group.Count() > 1); issues.AddRange(duplicateAnnotations.Select(duplicate => { diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs index 10ceffb07b..abb5502556 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs @@ -52,7 +52,7 @@ protected override IEnumerable DoGetInspectionResults() var annotations = State.AllAnnotations; var unboundAnnotations = UnboundAnnotations(annotations, userDeclarations, identifierReferences) - .Where(annotation => !annotation.MetaInformation.Target.HasFlag(AnnotationTarget.General) + .Where(annotation => !annotation.Annotation.Target.HasFlag(AnnotationTarget.General) || annotation.AnnotatedLine == null); var attributeAnnotationsInDocuments = AttributeAnnotationsInDocuments(userDeclarations); @@ -65,7 +65,7 @@ protected override IEnumerable DoGetInspectionResults() new QualifiedContext(annotation.QualifiedSelection.QualifiedName, annotation.Context))); } - private static IEnumerable UnboundAnnotations(IEnumerable annotations, IEnumerable userDeclarations, IEnumerable identifierReferences) + private static IEnumerable UnboundAnnotations(IEnumerable annotations, IEnumerable userDeclarations, IEnumerable identifierReferences) { var boundAnnotationsSelections = userDeclarations .SelectMany(declaration => declaration.Annotations) @@ -76,11 +76,11 @@ private static IEnumerable UnboundAnnotations(IEnumerable !boundAnnotationsSelections.Contains(annotation.QualifiedSelection)).ToList(); } - private static IEnumerable AttributeAnnotationsInDocuments(IEnumerable userDeclarations) + private static IEnumerable AttributeAnnotationsInDocuments(IEnumerable userDeclarations) { var declarationsInDocuments = userDeclarations .Where(declaration => declaration.QualifiedModuleName.ComponentType == ComponentType.Document); - return declarationsInDocuments.SelectMany(doc => doc.Annotations).OfType(); + return declarationsInDocuments.SelectMany(doc => doc.Annotations).Where(pta => pta.Annotation is IAttributeAnnotation); } } } \ No newline at end of file diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs index 3cddf6320d..5915a1de08 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs @@ -48,21 +48,21 @@ public MissingAttributeInspection(RubberduckParserState state) protected override IEnumerable DoGetInspectionResults() { var declarationsWithAttributeAnnotations = State.DeclarationFinder.AllUserDeclarations - .Where(declaration => declaration.Annotations.Any(annotation => annotation is IAttributeAnnotation)); + .Where(declaration => declaration.Annotations.Any(pta => pta.Annotation is IAttributeAnnotation)); var results = new List(); foreach (var declaration in declarationsWithAttributeAnnotations.Where(decl => decl.QualifiedModuleName.ComponentType != ComponentType.Document && !decl.IsIgnoringInspectionResultFor(AnnotationName))) { - foreach(var annotation in declaration.Annotations.OfType()) + foreach (var annotationInstance in declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation)) { - if (MissesCorrespondingAttribute(declaration, annotation)) + var annotation = (IAttributeAnnotation)annotationInstance.Annotation; + if (MissesCorrespondingAttribute(declaration, annotationInstance)) { - var description = string.Format(InspectionResults.MissingAttributeInspection, declaration.IdentifierName, - annotation.AnnotationType.ToString()); + var description = string.Format(InspectionResults.MissingAttributeInspection, declaration.IdentifierName, annotation.Name); var result = new DeclarationInspectionResult(this, description, declaration, - new QualifiedContext(declaration.QualifiedModuleName, annotation.Context)); - result.Properties.Annotation = annotation; + new QualifiedContext(declaration.QualifiedModuleName, annotationInstance.Context)); + result.Properties.Annotation = annotationInstance; results.Add(result); } @@ -72,9 +72,10 @@ protected override IEnumerable DoGetInspectionResults() return results; } - private static bool MissesCorrespondingAttribute(Declaration declaration, IAttributeAnnotation annotation) + private static bool MissesCorrespondingAttribute(Declaration declaration, ParseTreeAnnotation annotation) { - if (string.IsNullOrEmpty(annotation.Attribute)) + var attribute = annotation.Attribute(); + if (string.IsNullOrEmpty(attribute)) { return false; } diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs index 3b7b601555..35c1e98ca6 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs @@ -88,16 +88,15 @@ private static bool MissesCorrespondingMemberAnnotation(Declaration declaration, } var attributeBaseName = AttributeBaseName(declaration, attribute); - - //VB_Ext_Key attributes are special in that identity also depends on the first value, the key. + // VB_Ext_Key attributes are special in that identity also depends on the first value, the key. if (attributeBaseName == "VB_Ext_Key") { - return !declaration.Annotations.OfType() - .Any(annotation => annotation.Attribute.Equals("VB_Ext_Key") && attribute.Values[0].Equals(annotation.AttributeValues[0])); + return !declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation) + .Any(annotation => annotation.Attribute().Equals("VB_Ext_Key") && attribute.Values[0].Equals(annotation.AttributeValues()[0])); } - return !declaration.Annotations.OfType() - .Any(annotation => annotation.Attribute.Equals(attributeBaseName)); + return !declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation) + .Any(annotation => annotation.Attribute().Equals(attributeBaseName)); } private static string AttributeBaseName(Declaration declaration, AttributeNode attribute) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs index d5bd9d61be..05fab86ffa 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs @@ -93,16 +93,15 @@ private static bool MissesCorrespondingModuleAnnotation(Declaration declaration, { return false; } - //VB_Ext_Key attributes are special in that identity also depends on the first value, the key. if (attribute.Name == "VB_Ext_Key") { - return !declaration.Annotations.OfType() - .Any(annotation => annotation.Attribute.Equals("VB_Ext_Key") && attribute.Values[0].Equals(annotation.AttributeValues[0])); + return !declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation) + .Any(annotation => annotation.Attribute().Equals("VB_Ext_Key") && attribute.Values[0].Equals(annotation.AttributeValues()[0])); } - return !declaration.Annotations.OfType() - .Any(annotation => annotation.Attribute.Equals(attribute.Name)); + return !declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation) + .Any(annotation => annotation.Attribute().Equals(attribute.Name)); } } } \ No newline at end of file diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs index 70fd5e5cfa..f261a8aaef 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs @@ -39,7 +39,7 @@ public ModuleWithoutFolderInspection(RubberduckParserState state) protected override IEnumerable DoGetInspectionResults() { var modulesWithoutFolderAnnotation = State.DeclarationFinder.UserDeclarations(Parsing.Symbols.DeclarationType.Module) - .Where(w => !w.Annotations.OfType().Any()) + .Where(w => !w.Annotations.Any(pta => pta.Annotation is FolderAnnotation)) .ToList(); return modulesWithoutFolderAnnotation diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs index 895a53df30..94024512f2 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs @@ -58,13 +58,15 @@ protected override IEnumerable DoGetInspectionResults() { var declarations = State.AllUserDeclarations .Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Member) && - declaration.Annotations.OfType().Any()); + declaration.Annotations.Any(pta => pta.Annotation is ObsoleteAnnotation)); var issues = new List(); foreach (var declaration in declarations) { - var replacementDocumentation = declaration.Annotations.OfType().First().ReplacementDocumentation; + var replacementDocumentation = declaration.Annotations + .First(pta => pta.Annotation is ObsoleteAnnotation) + .AnnotationArguments.FirstOrDefault() ?? string.Empty; issues.AddRange(declaration.References.Select(reference => new IdentifierReferenceInspectionResult(this, diff --git a/Rubberduck.CodeAnalysis/Inspections/Extensions/IgnoreRelatedExtensions.cs b/Rubberduck.CodeAnalysis/Inspections/Extensions/IgnoreRelatedExtensions.cs index 548c4e9dc9..79c6c91c94 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Extensions/IgnoreRelatedExtensions.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Extensions/IgnoreRelatedExtensions.cs @@ -12,7 +12,7 @@ static class IgnoreRelatedExtensions public static bool IsIgnoringInspectionResultFor(this IdentifierReference reference, string inspectionName) { return reference.ParentScoping.HasModuleIgnoreFor(inspectionName) || - reference.Annotations.OfType().Any(ignore => ignore.IsIgnored(inspectionName)); + reference.Annotations.Any(ignore => ignore.Annotation is IgnoreAnnotation && ignore.AnnotationArguments.Contains(inspectionName)); } public static bool IsIgnoringInspectionResultFor(this Declaration declaration, string inspectionName) @@ -29,12 +29,13 @@ public static bool IsIgnoringInspectionResultFor(this QualifiedContext parserCon { return parserContext.ModuleName.IsIgnoringInspectionResultFor(parserContext.Context.Start.Line, declarationFinder, inspectionName); } + private static bool IsIgnoringInspectionResultFor(this QualifiedModuleName module, int line, DeclarationFinder declarationFinder, string inspectionName) { - var lineScopedAnnotations = declarationFinder.FindAnnotations(module, line).OfType(); + var lineScopedAnnotations = declarationFinder.FindAnnotations(module, line); var moduleDeclaration = declarationFinder.Members(module).First(decl => decl.DeclarationType.HasFlag(DeclarationType.Module)); - var isLineIgnored = lineScopedAnnotations.Any(annotation => annotation.IsIgnored(inspectionName)); + var isLineIgnored = lineScopedAnnotations.Any(annotation => annotation.AnnotationArguments.Contains(inspectionName)); var isModuleIgnored = moduleDeclaration.HasModuleIgnoreFor(inspectionName); return isLineIgnored || isModuleIgnored; @@ -43,15 +44,15 @@ private static bool IsIgnoringInspectionResultFor(this QualifiedModuleName modul private static bool HasModuleIgnoreFor(this Declaration declaration, string inspectionName) { return Declaration.GetModuleParent(declaration)?.Annotations - .OfType() - .Any(ignoreModule => ignoreModule.IsIgnored(inspectionName)) ?? false; + .Where(pta => pta.Annotation is IgnoreModuleAnnotation) + .Any(ignoreModule => !ignoreModule.AnnotationArguments.Any() || ignoreModule.AnnotationArguments.Contains(inspectionName)) ?? false; } private static bool HasIgnoreFor(this Declaration declaration, string inspectionName) { return declaration?.Annotations - .OfType() - .Any(ignore => ignore.IsIgnored(inspectionName)) ?? false; + .Where(pta => pta.Annotation is IgnoreAnnotation) + .Any(ignore => ignore.AnnotationArguments.Contains(inspectionName)) ?? false; } } } diff --git a/Rubberduck.CodeAnalysis/QuickFixes/AddMissingAttributeQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/AddMissingAttributeQuickFix.cs index 9a9850b970..1c075b6391 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/AddMissingAttributeQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/AddMissingAttributeQuickFix.cs @@ -22,13 +22,13 @@ public AddMissingAttributeQuickFix(IAttributesUpdater attributesUpdater) public override void Fix(IInspectionResult result, IRewriteSession rewriteSession) { var declaration = result.Target; - IAttributeAnnotation annotation = result.Properties.Annotation; - + ParseTreeAnnotation annotationInstance = result.Properties.Annotation; + var attribute = annotationInstance.Attribute(); var attributeName = declaration.DeclarationType.HasFlag(DeclarationType.Module) - ? annotation.Attribute - : $"{declaration.IdentifierName}.{annotation.Attribute}"; + ? attribute + : $"{declaration.IdentifierName}.{attribute}"; - _attributesUpdater.AddAttribute(rewriteSession, declaration, attributeName, annotation.AttributeValues); + _attributesUpdater.AddAttribute(rewriteSession, declaration, attributeName, annotationInstance.AttributeValues()); } public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.AddMissingAttributeQuickFix; diff --git a/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeAnnotationQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeAnnotationQuickFix.cs index abdca1cde4..fe28d30c3b 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeAnnotationQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeAnnotationQuickFix.cs @@ -25,7 +25,7 @@ public AdjustAttributeAnnotationQuickFix(IAnnotationUpdater annotationUpdater, I public override void Fix(IInspectionResult result, IRewriteSession rewriteSession) { - IAttributeAnnotation oldAnnotation = result.Properties.Annotation; + ParseTreeAnnotation oldAnnotation = result.Properties.Annotation; string attributeName = result.Properties.AttributeName; IReadOnlyList attributeValues = result.Properties.AttributeValues; diff --git a/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeValuesQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeValuesQuickFix.cs index a3ca5b34b3..54e2fe228a 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeValuesQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeValuesQuickFix.cs @@ -24,14 +24,16 @@ public AdjustAttributeValuesQuickFix(IAttributesUpdater attributesUpdater) public override void Fix(IInspectionResult result, IRewriteSession rewriteSession) { var declaration = result.Target; - IAttributeAnnotation annotation = result.Properties.Annotation; + ParseTreeAnnotation annotationInstance = result.Properties.Annotation; + IAttributeAnnotation annotation = (IAttributeAnnotation)annotationInstance.Annotation; IReadOnlyList attributeValues = result.Properties.AttributeValues; + var attribute = annotationInstance.Attribute(); var attributeName = declaration.DeclarationType.HasFlag(DeclarationType.Module) - ? annotation.Attribute - : $"{declaration.IdentifierName}.{annotation.Attribute}"; + ? attribute + : $"{declaration.IdentifierName}.{attribute}"; - _attributesUpdater.UpdateAttribute(rewriteSession, declaration, attributeName, annotation.AttributeValues, attributeValues); + _attributesUpdater.UpdateAttribute(rewriteSession, declaration, attributeName, annotationInstance.AttributeValues(), oldValues: attributeValues); } public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.AdjustAttributeValuesQuickFix; diff --git a/Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs index 191c5f6d6e..38525a4a64 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs @@ -49,13 +49,13 @@ private void FixNonModule(IInspectionResult result, IRewriteSession rewriteSessi var module = result.QualifiedSelection.QualifiedName; var lineToAnnotate = result.QualifiedSelection.Selection.StartLine; var existingIgnoreAnnotation = _state.DeclarationFinder.FindAnnotations(module, lineToAnnotate) - .OfType() + .Where(pta => pta.Annotation is IgnoreAnnotation) .FirstOrDefault(); - var annotationInfo = typeof(IgnoreAnnotation).GetCustomAttributes(false).OfType().Single(); + var annotationInfo = new IgnoreAnnotation(); if (existingIgnoreAnnotation != null) { - var annotationValues = existingIgnoreAnnotation.InspectionNames.ToList(); + var annotationValues = existingIgnoreAnnotation.AnnotationArguments.ToList(); annotationValues.Insert(0, result.Inspection.AnnotationName); _annotationUpdater.UpdateAnnotation(rewriteSession, existingIgnoreAnnotation, annotationInfo, annotationValues); } @@ -70,13 +70,13 @@ private void FixModule(IInspectionResult result, IRewriteSession rewriteSession) { var moduleDeclaration = result.Target; var existingIgnoreModuleAnnotation = moduleDeclaration.Annotations - .OfType() + .Where(pta => pta.Annotation is IgnoreModuleAnnotation) .FirstOrDefault(); - var annotationType = typeof(IgnoreModuleAnnotation).GetCustomAttributes(false).OfType().Single(); + var annotationType = new IgnoreModuleAnnotation(); if (existingIgnoreModuleAnnotation != null) { - var annotationValues = existingIgnoreModuleAnnotation.InspectionNames.ToList(); + var annotationValues = existingIgnoreModuleAnnotation.AnnotationArguments.ToList(); annotationValues.Insert(0, result.Inspection.AnnotationName); _annotationUpdater.UpdateAnnotation(rewriteSession, existingIgnoreModuleAnnotation, annotationType, annotationValues); } diff --git a/Rubberduck.CodeAnalysis/QuickFixes/RemoveDuplicatedAnnotationQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/RemoveDuplicatedAnnotationQuickFix.cs index 1b78d7f910..8832112462 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/RemoveDuplicatedAnnotationQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/RemoveDuplicatedAnnotationQuickFix.cs @@ -20,8 +20,8 @@ public RemoveDuplicatedAnnotationQuickFix(IAnnotationUpdater annotationUpdater) public override void Fix(IInspectionResult result, IRewriteSession rewriteSession) { var duplicateAnnotations = result.Target.Annotations - .Where(annotation => annotation.GetType() == result.Properties.AnnotationType) - .OrderBy(annotation => annotation.Context.Start.StartIndex) + .Where(pta => pta.Annotation == result.Properties.AnnotationType) + .OrderBy(annotation => annotation.AnnotatedLine) .Skip(1) .ToList(); diff --git a/Rubberduck.Core/UI/CodeExplorer/Commands/IndentCommand.cs b/Rubberduck.Core/UI/CodeExplorer/Commands/IndentCommand.cs index b2eea3f967..b662139148 100644 --- a/Rubberduck.Core/UI/CodeExplorer/Commands/IndentCommand.cs +++ b/Rubberduck.Core/UI/CodeExplorer/Commands/IndentCommand.cs @@ -53,14 +53,14 @@ private bool SpecialEvaluateCanExecute(object parameter) case CodeExplorerProjectViewModel project: return _state.AllUserDeclarations .Any(c => c.DeclarationType.HasFlag(DeclarationType.Module) && - !c.Annotations.Any(a => a is NoIndentAnnotation) && + !c.Annotations.Any(pta => pta.Annotation is NoIndentAnnotation) && c.ProjectId == project.Declaration.ProjectId); case CodeExplorerCustomFolderViewModel folder: return folder.Children.OfType() //TODO - this has the filter applied. .Select(s => s.Declaration) - .Any(d => !d.Annotations.Any(a => a is NoIndentAnnotation)); + .Any(d => !d.Annotations.Any(pta => pta.Annotation is NoIndentAnnotation)); case CodeExplorerComponentViewModel model: - return !model.Declaration.Annotations.Any(a => a is NoIndentAnnotation); + return !model.Declaration.Annotations.Any(pta => pta.Annotation is NoIndentAnnotation); case CodeExplorerMemberViewModel member: return member.QualifiedSelection.HasValue; default: @@ -85,7 +85,7 @@ protected override void OnExecute(object parameter) var componentDeclarations = _state.AllUserDeclarations.Where(c => c.DeclarationType.HasFlag(DeclarationType.Module) && - !c.Annotations.Any(a => a is NoIndentAnnotation) && + !c.Annotations.Any(pta => pta.Annotation is NoIndentAnnotation) && c.ProjectId == declaration.ProjectId); foreach (var componentDeclaration in componentDeclarations) @@ -99,7 +99,7 @@ protected override void OnExecute(object parameter) { var components = folder.Children.OfType() //TODO: this has the filter applied. .Select(s => s.Declaration) - .Where(d => !d.Annotations.Any(a => a is NoIndentAnnotation)) + .Where(d => !d.Annotations.Any(pta => pta.Annotation is NoIndentAnnotation)) .Select(d => _state.ProjectsProvider.Component(d.QualifiedName.QualifiedModuleName)); foreach (var component in components) diff --git a/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodCommand.cs b/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodCommand.cs index 656ce78251..1cec56eb9c 100644 --- a/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodCommand.cs +++ b/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodCommand.cs @@ -53,7 +53,7 @@ private bool SpecialEvaluateCanExecute(object parameter) var testModules = _state.AllUserDeclarations.Where(d => d.DeclarationType == DeclarationType.ProceduralModule && - d.Annotations.Any(a => a is TestModuleAnnotation)); + d.Annotations.Any(pta => pta.Annotation is TestModuleAnnotation)); try { diff --git a/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodExpectedErrorCommand.cs b/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodExpectedErrorCommand.cs index fd6b99c8d4..1999bce4a1 100644 --- a/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodExpectedErrorCommand.cs +++ b/Rubberduck.Core/UI/UnitTesting/ComCommands/AddTestMethodExpectedErrorCommand.cs @@ -47,7 +47,7 @@ private bool SpecialEvaluateCanExecute(object parameter) } var testModules = _state.AllUserDeclarations.Where(d => d.DeclarationType == DeclarationType.ProceduralModule && - d.Annotations.Any(a => a is TestModuleAnnotation)); + d.Annotations.Any(pta => pta.Annotation is TestModuleAnnotation)); try { diff --git a/Rubberduck.Core/UI/UnitTesting/TestExplorerViewModel.cs b/Rubberduck.Core/UI/UnitTesting/TestExplorerViewModel.cs index ab143751c9..683f77bb37 100644 --- a/Rubberduck.Core/UI/UnitTesting/TestExplorerViewModel.cs +++ b/Rubberduck.Core/UI/UnitTesting/TestExplorerViewModel.cs @@ -377,7 +377,7 @@ private void ExecuteIgnoreTestCommand(object parameter) { var rewriteSession = RewritingManager.CheckOutCodePaneSession(); - AnnotationUpdater.AddAnnotation(rewriteSession, _mousedOverTestMethod.Declaration, typeof(IgnoreTestAnnotation).GetCustomAttributes(false).OfType().Single()); + AnnotationUpdater.AddAnnotation(rewriteSession, _mousedOverTestMethod.Declaration, new IgnoreTestAnnotation()); rewriteSession.TryRewrite(); } @@ -386,7 +386,7 @@ private void ExecuteUnignoreTestCommand(object parameter) { var rewriteSession = RewritingManager.CheckOutCodePaneSession(); var ignoreTestAnnotations = _mousedOverTestMethod.Declaration.Annotations - .Where(iannotations => iannotations is IgnoreTestAnnotation); + .Where(pta => pta.Annotation is IgnoreTestAnnotation); foreach (var ignoreTestAnnotation in ignoreTestAnnotations) { diff --git a/Rubberduck.Main/Root/RubberduckIoCInstaller.cs b/Rubberduck.Main/Root/RubberduckIoCInstaller.cs index 2574059068..d625949907 100644 --- a/Rubberduck.Main/Root/RubberduckIoCInstaller.cs +++ b/Rubberduck.Main/Root/RubberduckIoCInstaller.cs @@ -928,7 +928,10 @@ private void RegisterParsingEngine(IWindsorContainer container) container.Register(Component.For() .ImplementedBy() .DependsOn(Dependency.OnComponent("codePaneSourceCodeProvider", "CodeModuleSourceCodeHandler"), - Dependency.OnComponent("attributesSourceCodeProvider", "SourceFileSourceCodeHandler")) + Dependency.OnComponent("attributesSourceCodeProvider", "SourceFileSourceCodeHandler") + // TODO not sure whether this explicit registration is necessary + //,Dependency.OnComponent(typeof(IAnnotationFactory), typeof(VBAParserAnnotationFactory)) + ) .LifestyleSingleton()); container.Register(Component.For() .ImplementedBy() diff --git a/Rubberduck.Parsing/Annotations/AnnotationBase.cs b/Rubberduck.Parsing/Annotations/AnnotationBase.cs index 6f53013f43..a0d4eb3635 100644 --- a/Rubberduck.Parsing/Annotations/AnnotationBase.cs +++ b/Rubberduck.Parsing/Annotations/AnnotationBase.cs @@ -7,47 +7,15 @@ namespace Rubberduck.Parsing.Annotations { public abstract class AnnotationBase : IAnnotation { - public const string ANNOTATION_MARKER = "@"; + public bool AllowMultiple { get; } + public string Name { get; } + public AnnotationTarget Target { get; } - private readonly Lazy _annotatedLine; - - protected AnnotationBase(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context) - { - QualifiedSelection = qualifiedSelection; - Context = context; - _annotatedLine = new Lazy(GetAnnotatedLine); - MetaInformation = GetType().GetCustomAttributes(false).OfType().Single(); - } - - public QualifiedSelection QualifiedSelection { get; } - public VBAParser.AnnotationContext Context { get; } - // sigh... we kinda want to seal this, but can't because it's not inherited from a class... - public AnnotationAttribute MetaInformation { get; } - public string AnnotationType => MetaInformation.Name; - - public int? AnnotatedLine => _annotatedLine.Value; - - public override string ToString() => $"Annotation Type: {GetType()}"; - - private int? GetAnnotatedLine() + public AnnotationBase(string name, AnnotationTarget target, bool allowMultiple = false) { - var enclosingEndOfStatement = Context.GetAncestor(); - - //Annotations on the same line as non-whitespace statements do not scope to anything. - if (enclosingEndOfStatement.Start.TokenIndex != 0) - { - var firstEndOfLine = enclosingEndOfStatement.GetFirstEndOfLine(); - var parentEndOfLine = Context.GetAncestor(); - if (firstEndOfLine.Equals(parentEndOfLine)) - { - return null; - } - } - - var lastToken = enclosingEndOfStatement.stop; - return lastToken.Type == VBAParser.NEWLINE - ? lastToken.Line + 1 - : lastToken.Line; + Name = name; + Target = target; + AllowMultiple = allowMultiple; } } } diff --git a/Rubberduck.Parsing/Annotations/AnnotationListener.cs b/Rubberduck.Parsing/Annotations/AnnotationListener.cs index 6e4f095f6a..14ef9c606e 100644 --- a/Rubberduck.Parsing/Annotations/AnnotationListener.cs +++ b/Rubberduck.Parsing/Annotations/AnnotationListener.cs @@ -7,18 +7,18 @@ namespace Rubberduck.Parsing.Annotations { public sealed class AnnotationListener : VBAParserBaseListener { - private readonly List _annotations; + private readonly List _annotations; private readonly IAnnotationFactory _factory; private readonly QualifiedModuleName _qualifiedName; public AnnotationListener(IAnnotationFactory factory, QualifiedModuleName qualifiedName) { - _annotations = new List(); + _annotations = new List(); _factory = factory; _qualifiedName = qualifiedName; } - public IEnumerable Annotations => _annotations; + public IEnumerable Annotations => _annotations; public override void ExitAnnotation([NotNull] VBAParser.AnnotationContext context) { diff --git a/Rubberduck.Parsing/Annotations/AttributeAnnotationExtensions.cs b/Rubberduck.Parsing/Annotations/AttributeAnnotationExtensions.cs new file mode 100644 index 0000000000..de7beddc69 --- /dev/null +++ b/Rubberduck.Parsing/Annotations/AttributeAnnotationExtensions.cs @@ -0,0 +1,30 @@ +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Threading.Tasks; + +namespace Rubberduck.Parsing.Annotations +{ + public static class AttributeAnnotationExtensions + { + public static string Attribute(this ParseTreeAnnotation annotationInstance) + { + if (annotationInstance.Annotation is IAttributeAnnotation annotation) + { + return annotation.Attribute(annotationInstance.AnnotationArguments); + } + return null; + } + + public static IReadOnlyList AttributeValues(this ParseTreeAnnotation annotationInstance) + { + if (annotationInstance.Annotation is IAttributeAnnotation annotation) + { + return annotation.AnnotationToAttributeValues(annotationInstance.AnnotationArguments); + } + return null; + + } + } +} diff --git a/Rubberduck.Parsing/Annotations/AttributeAnnotationProvider.cs b/Rubberduck.Parsing/Annotations/AttributeAnnotationProvider.cs index 672b99f566..37871f7640 100644 --- a/Rubberduck.Parsing/Annotations/AttributeAnnotationProvider.cs +++ b/Rubberduck.Parsing/Annotations/AttributeAnnotationProvider.cs @@ -9,122 +9,61 @@ public class AttributeAnnotationProvider : IAttributeAnnotationProvider { // I want to const this, but can't private readonly AnnotationTarget [] distinctTargets = new AnnotationTarget[] { AnnotationTarget.Identifier, AnnotationTarget.Member, AnnotationTarget.Module, AnnotationTarget.Variable }; - private readonly Dictionary> annotationInfoByTarget - = new Dictionary>(); + private readonly Dictionary> annotationInfoByTarget + = new Dictionary>(); - // FIXME make sure only AttributeAnnotations are injected here - public AttributeAnnotationProvider(IEnumerable attributeAnnotationTypes) + private readonly IAttributeAnnotation memberFallback = new MemberAttributeAnnotation(); + private readonly IAttributeAnnotation moduleFallback = new ModuleAttributeAnnotation(); + + public AttributeAnnotationProvider(IEnumerable attributeAnnotations) { // set up empty lists to put information into foreach (var validTarget in distinctTargets) { - annotationInfoByTarget[validTarget] = new List(); + annotationInfoByTarget[validTarget] = new List(); } - // we're defensively filtering, but theoretically this might be CW's job? - foreach (var annotationType in attributeAnnotationTypes.Where(type => type.GetInterfaces().Contains(typeof(IAttributeAnnotation)))) + + foreach (var annotation in attributeAnnotations) { - // Extract the static information about the annotation type from it's AnnotationAttribute - var staticInfo = annotationType.GetCustomAttributes(false) - .OfType() - .Single(); foreach (var validTarget in distinctTargets) { - if (staticInfo.Target.HasFlag(validTarget)) + if (annotation.Target.HasFlag(validTarget)) { - annotationInfoByTarget[validTarget].Add(annotationType); + annotationInfoByTarget[validTarget].Add(annotation); } } } } - public (AnnotationAttribute annotationInfo, IReadOnlyList values) MemberAttributeAnnotation(string attributeBaseName, IReadOnlyList attributeValues) + public (IAttributeAnnotation annotation, IReadOnlyList annotationValues) MemberAttributeAnnotation(string attributeBaseName, IReadOnlyList attributeValues) { - // quasi-const - var fallbackType = typeof(MemberAttributeAnnotation); // go through all non-module annotations (contrary to only member annotations) var memberAnnotationTypes = annotationInfoByTarget[AnnotationTarget.Member] .Concat(annotationInfoByTarget[AnnotationTarget.Variable]) .Concat(annotationInfoByTarget[AnnotationTarget.Identifier]); - foreach (var type in memberAnnotationTypes) + foreach (var annotation in memberAnnotationTypes) { - if (MatchesAttributeNameAndValue(type, attributeBaseName, attributeValues, out var codePassAnnotationValues)) + if (annotation.MatchesAttributeDefinition(attributeBaseName, attributeValues)) { - return (GetAttribute(type), codePassAnnotationValues); + return (annotation, annotation.AttributeToAnnotationValues(attributeValues)); } } - return BuildFallback(attributeBaseName, attributeValues, fallbackType); + var fallbackAttributeArguments = new[] { attributeBaseName }.Concat(attributeValues); + return (memberFallback, memberFallback.AttributeToAnnotationValues(fallbackAttributeArguments.ToList())); } - public (AnnotationAttribute annotationInfo, IReadOnlyList values) ModuleAttributeAnnotation(string attributeName, IReadOnlyList attributeValues) + public (IAttributeAnnotation annotation, IReadOnlyList annotationValues) ModuleAttributeAnnotation(string attributeName, IReadOnlyList attributeValues) { - // quasi-const - var fallbackType = typeof(ModuleAttributeAnnotation); var moduleAnnotationTypes = annotationInfoByTarget[AnnotationTarget.Module]; - foreach (var type in moduleAnnotationTypes) - { - if (MatchesAttributeNameAndValue(type, attributeName, attributeValues, out var codePassAnnotationValues)) - { - return (GetAttribute(type), codePassAnnotationValues); - } - } - return BuildFallback(attributeName, attributeValues, fallbackType); - } - - private bool MatchesAttributeNameAndValue(Type type, string attributeName, IReadOnlyList attributeValues, out IReadOnlyList codePassAnnotationValues) - { - codePassAnnotationValues = attributeValues; - if (typeof(FlexibleAttributeAnnotationBase).IsAssignableFrom(type)) - { - // this is always the fallback case, which must only be accepted if all other options are exhausted. - return false; - } - if (typeof(FixedAttributeValueAnnotationBase).IsAssignableFrom(type)) - { - var attributeInfo = GetAttribute(type); - if (attributeInfo.AttributeName.Equals(attributeName, StringComparison.OrdinalIgnoreCase) - && attributeInfo.AttributeValues.SequenceEqual(attributeValues)) - { - // there is no way to set a value in the annotation, therefore we discard the attribute values - codePassAnnotationValues = new List(); - return true; - } - } - if (typeof(FlexibleAttributeValueAnnotationBase).IsAssignableFrom(type)) + foreach (var annotation in moduleAnnotationTypes) { - // obtain flexible attribute information - var attributeInfo = GetAttribute(type); - if (attributeInfo.AttributeName.Equals(attributeName, StringComparison.OrdinalIgnoreCase) - && attributeInfo.NumberOfParameters == attributeValues.Count) + if (annotation.MatchesAttributeDefinition(attributeName, attributeValues)) { - if (attributeInfo.HasCustomTransformation) - { - try { - // dispatch to custom transformation - codePassAnnotationValues = ((IEnumerable)type.GetMethod("TransformToAnnotationValues", new[] { typeof(IEnumerable) }) - .Invoke(null, new[] { attributeValues })).ToList(); - } - catch (Exception) - { - codePassAnnotationValues = attributeValues; - } - } - return true; + return (annotation, annotation.AttributeToAnnotationValues(attributeValues)); } } - return false; - } - - private (AnnotationAttribute annotationInfo, IReadOnlyList values) BuildFallback(string attributeBaseName, IReadOnlyList attributeValues, Type fallbackType) - { - var fallbackValues = new[] { attributeBaseName }.Concat(attributeValues).ToList(); - return (GetAttribute(fallbackType), fallbackValues); - } - - private static T GetAttribute(Type annotationType) - { - return annotationType.GetCustomAttributes(false) - .OfType() - .Single(); + var fallbackAttributeArguments = new[] { attributeName }.Concat(attributeValues); + return (moduleFallback, moduleFallback.AttributeToAnnotationValues(fallbackAttributeArguments.ToList())); } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/IAnnotation.cs b/Rubberduck.Parsing/Annotations/IAnnotation.cs index 6274cefba9..21718f4849 100644 --- a/Rubberduck.Parsing/Annotations/IAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/IAnnotation.cs @@ -6,27 +6,9 @@ namespace Rubberduck.Parsing.Annotations { public interface IAnnotation { - QualifiedSelection QualifiedSelection { get; } - VBAParser.AnnotationContext Context { get; } - int? AnnotatedLine { get; } - AnnotationAttribute MetaInformation { get; } - - string AnnotationType { get; } - } - - [AttributeUsage(AttributeTargets.Class, AllowMultiple = false, Inherited = false)] - public class AnnotationAttribute : Attribute - { - public string Name { get; } - public AnnotationTarget Target { get; } - public bool AllowMultiple { get; } - - public AnnotationAttribute(string name, AnnotationTarget target, bool allowMultiple = false) - { - Name = name; - Target = target; - AllowMultiple = allowMultiple; - } + string Name { get; } + AnnotationTarget Target { get; } + bool AllowMultiple { get; } } [Flags] diff --git a/Rubberduck.Parsing/Annotations/IAnnotationFactory.cs b/Rubberduck.Parsing/Annotations/IAnnotationFactory.cs index d18d663813..d0a50d1b67 100644 --- a/Rubberduck.Parsing/Annotations/IAnnotationFactory.cs +++ b/Rubberduck.Parsing/Annotations/IAnnotationFactory.cs @@ -5,6 +5,6 @@ namespace Rubberduck.Parsing.Annotations { public interface IAnnotationFactory { - IAnnotation Create(VBAParser.AnnotationContext context, QualifiedSelection qualifiedSelection); + ParseTreeAnnotation Create(VBAParser.AnnotationContext context, QualifiedSelection qualifiedSelection); } } diff --git a/Rubberduck.Parsing/Annotations/IAttributeAnnotation.cs b/Rubberduck.Parsing/Annotations/IAttributeAnnotation.cs index 9e71b0afa7..0878aada4d 100644 --- a/Rubberduck.Parsing/Annotations/IAttributeAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/IAttributeAnnotation.cs @@ -5,48 +5,10 @@ namespace Rubberduck.Parsing.Annotations { public interface IAttributeAnnotation : IAnnotation { - string Attribute { get; } - IReadOnlyList AttributeValues { get; } - } - // attributes are disjoint to avoid issues around security and multiple attributes - [AttributeUsage(AttributeTargets.Class, AllowMultiple = false, Inherited = false)] - public class FixedAttributeValueAnnotationAttribute : Attribute - { - /// - /// Enum value is associated with a VB_Attribute with a fixed value. - /// - /// The name of the associated attribute. - /// If specified, constrains the association to a specific value. - public FixedAttributeValueAnnotationAttribute(string name, params string[] values) - { - AttributeName = name; - AttributeValues = values; - } - - public string AttributeName { get; } - public IReadOnlyList AttributeValues { get; } - } - - [AttributeUsage(AttributeTargets.Class, AllowMultiple = false, Inherited = false)] - public class FlexibleAttributeValueAnnotationAttribute : Attribute - { - /// - /// Enum value is associated with a VB_Attribute with a fixed number of values taken from the annotation values. - /// - /// The name of the associated attribute. - /// Size of the attribute value list the attribute takes. - /// - /// A function used during parsing to transform the values stored in the exported attribute to those stored in the code pass annotation arguments. - /// - public FlexibleAttributeValueAnnotationAttribute(string name, int numberOfParameters, bool hasCustomTransform = false) - { - AttributeName = name; - NumberOfParameters = numberOfParameters; - HasCustomTransformation = hasCustomTransform; - } + bool MatchesAttributeDefinition(string attributeName, IReadOnlyList attributeValues); + string Attribute(IReadOnlyList annotationValues); - public string AttributeName { get; } - public int NumberOfParameters { get; } - public bool HasCustomTransformation { get; } + IReadOnlyList AnnotationToAttributeValues(IReadOnlyList annotationValues); + IReadOnlyList AttributeToAnnotationValues(IReadOnlyList attributeValues); } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/IAttributeAnnotationProvider.cs b/Rubberduck.Parsing/Annotations/IAttributeAnnotationProvider.cs index bb155c5a46..0f1ec23b29 100644 --- a/Rubberduck.Parsing/Annotations/IAttributeAnnotationProvider.cs +++ b/Rubberduck.Parsing/Annotations/IAttributeAnnotationProvider.cs @@ -4,7 +4,7 @@ namespace Rubberduck.Parsing.Annotations { public interface IAttributeAnnotationProvider { - (AnnotationAttribute annotationInfo, IReadOnlyList values) ModuleAttributeAnnotation(string attributeName, IReadOnlyList attributeValues); - (AnnotationAttribute annotationInfo, IReadOnlyList values) MemberAttributeAnnotation(string attributeBaseName, IReadOnlyList attributeValues); + (IAttributeAnnotation annotation, IReadOnlyList annotationValues) ModuleAttributeAnnotation(string attributeName, IReadOnlyList attributeValues); + (IAttributeAnnotation annotation, IReadOnlyList annotationValues) MemberAttributeAnnotation(string attributeBaseName, IReadOnlyList attributeValues); } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/DefaultMemberAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/DefaultMemberAnnotation.cs index 9f61332910..32183fc0b6 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/DefaultMemberAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/DefaultMemberAnnotation.cs @@ -8,17 +8,11 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for specifying a member's VB_UserMemId attribute value. /// - /// - [Annotation("DefaultMember", AnnotationTarget.Member)] - [FixedAttributeValueAnnotation("VB_UserMemId", "0")] public sealed class DefaultMemberAnnotation : FixedAttributeValueAnnotationBase { - public DefaultMemberAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(qualifiedSelection, context) + public DefaultMemberAnnotation() + : base("DefaultMember", AnnotationTarget.Member, "VB_UserMemId", new[] { "0" }) { - Description = parameters?.FirstOrDefault() ?? string.Empty; } - - public string Description { get; } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/DescriptionAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/DescriptionAnnotation.cs index 70d42d4b58..1bbed06265 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/DescriptionAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/DescriptionAnnotation.cs @@ -7,12 +7,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for specifying a member's VB_Description attribute. /// - [Annotation("Description", AnnotationTarget.Member)] - [FlexibleAttributeValueAnnotation("VB_Description", 1)] public sealed class DescriptionAnnotation : DescriptionAttributeAnnotationBase { - public DescriptionAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(qualifiedSelection, context, parameters) + public DescriptionAnnotation() + : base("Description", AnnotationTarget.Member, "VB_Description", 1) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/DescriptionAttributeAnnotationBase.cs b/Rubberduck.Parsing/Annotations/Implementations/DescriptionAttributeAnnotationBase.cs index da27b85509..6c42023eea 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/DescriptionAttributeAnnotationBase.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/DescriptionAttributeAnnotationBase.cs @@ -7,17 +7,8 @@ namespace Rubberduck.Parsing.Annotations { public abstract class DescriptionAttributeAnnotationBase : FlexibleAttributeValueAnnotationBase { - public DescriptionAttributeAnnotationBase(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable attributeValues) - : base(qualifiedSelection, context, attributeValues?.Take(1).ToList()) - { - Description = AttributeValues?.FirstOrDefault(); - if ((Description?.StartsWith("\"") ?? false) && Description.EndsWith("\"")) - { - // strip surrounding double quotes - Description = Description.Substring(1, Description.Length - 2); - } - } - - public string Description { get; } + public DescriptionAttributeAnnotationBase(string name, AnnotationTarget target, string attribute, int valueCount) + : base(name, target, attribute, valueCount) + { } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/EnumeratorMemberAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/EnumeratorMemberAnnotation.cs index 4b5af09ac3..ada28d3157 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/EnumeratorMemberAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/EnumeratorMemberAnnotation.cs @@ -7,12 +7,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for specifying a member's VB_UserMemId attribute value. /// - [Annotation("Enumerator", AnnotationTarget.Member)] - [FixedAttributeValueAnnotation("VB_UserMemId", "-4")] public sealed class EnumeratorMemberAnnotation : FixedAttributeValueAnnotationBase { - public EnumeratorMemberAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(qualifiedSelection, context) + public EnumeratorMemberAnnotation() + : base("Enumerator", AnnotationTarget.Member, "VB_UserMemId", new[] { "-4" }) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/ExcelHotKeyAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ExcelHotKeyAnnotation.cs index 5a65682db9..662aa4c2e7 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/ExcelHotKeyAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/ExcelHotKeyAnnotation.cs @@ -7,18 +7,19 @@ namespace Rubberduck.Parsing.Annotations { - [Annotation("ExcelHotkey", AnnotationTarget.Member)] - [FlexibleAttributeValueAnnotation("VB_ProcData.VB_Invoke_Func", 1, true)] public sealed class ExcelHotKeyAnnotation : FlexibleAttributeValueAnnotationBase { - public ExcelHotKeyAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable annotationParameterValues) : - base(qualifiedSelection, context, GetHotKeyAttributeValue(annotationParameterValues)) + public ExcelHotKeyAnnotation() + : base("ExcelHotkey", AnnotationTarget.Member, "VB_ProcData.VB_Invoke_Func", 1) { } - - private static IEnumerable GetHotKeyAttributeValue(IEnumerable parameters) => - parameters.Take(1).Select(v => v.UnQuote()[0] + @"\n14".EnQuote()).ToList(); - - public static IEnumerable TransformToAnnotationValues(IEnumerable attributeValues) => - attributeValues.Select(keySpec => keySpec.UnQuote().Substring(0, 1)); + public override IReadOnlyList AnnotationToAttributeValues(IReadOnlyList annotationValues) + { + return annotationValues.Take(1).Select(v => v.UnQuote()[0] + @"\n14".EnQuote()).ToList(); + } + + public override IReadOnlyList AttributeToAnnotationValues(IReadOnlyList attributeValues) + { + return attributeValues.Select(keySpec => keySpec.UnQuote().Substring(0, 1)).ToList(); + } } } diff --git a/Rubberduck.Parsing/Annotations/Implementations/ExposedModuleAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ExposedModuleAnnotation.cs index 490d9d4116..3ba70ee34f 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/ExposedModuleAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/ExposedModuleAnnotation.cs @@ -7,12 +7,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for specifying a module's VB_Exposed attribute. /// - [Annotation("Exposed", AnnotationTarget.Module)] - [FixedAttributeValueAnnotation("VB_Exposed", "True")] public sealed class ExposedModuleAnnotation : FixedAttributeValueAnnotationBase { - public ExposedModuleAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(qualifiedSelection, context) + public ExposedModuleAnnotation() + : base("Exposed", AnnotationTarget.Module, "VB_Exposed", new[] { "True" }) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/FixedAttributeValueAnnotationBase.cs b/Rubberduck.Parsing/Annotations/Implementations/FixedAttributeValueAnnotationBase.cs index b01d7fa7ba..901475a37f 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/FixedAttributeValueAnnotationBase.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/FixedAttributeValueAnnotationBase.cs @@ -8,29 +8,36 @@ namespace Rubberduck.Parsing.Annotations { public abstract class FixedAttributeValueAnnotationBase : AnnotationBase, IAttributeAnnotation { - protected FixedAttributeValueAnnotationBase(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context) - : base(qualifiedSelection, context) + private readonly string attribute; + private readonly IReadOnlyList attributeValues; + + protected FixedAttributeValueAnnotationBase(string name, AnnotationTarget target, string attribute, IEnumerable attributeValues, bool allowMultiple = false) + : base(name, target, allowMultiple) { - var fixedAttributeValueInfo = FixedAttributeValueInfo(GetType()); + // IEnumerable makes specifying the compile-time constant list easier on us + this.attributeValues = attributeValues.ToList(); + this.attribute = attribute; + } - Attribute = fixedAttributeValueInfo.attribute; - AttributeValues = fixedAttributeValueInfo.attributeValues; + public IReadOnlyList AnnotationToAttributeValues(IReadOnlyList annotationValues) + { + return attributeValues; } - public string Attribute { get; } - public IReadOnlyList AttributeValues { get; } + public string Attribute(IReadOnlyList annotationValues) + { + return attribute; + } - private static (string attribute, IReadOnlyList attributeValues) FixedAttributeValueInfo(Type annotationType) + public IReadOnlyList AttributeToAnnotationValues(IReadOnlyList attributeValues) { - var attributeValueInfo = annotationType.GetCustomAttributes(false) - .OfType() - .SingleOrDefault(); - if (attributeValueInfo == null) - { - return ("", new List()); - } + // annotation values must not be specified, because attribute values are fixed in the first place + return new List(); + } - return (attributeValueInfo.AttributeName, attributeValueInfo.AttributeValues); + public bool MatchesAttributeDefinition(string attributeName, IReadOnlyList attributeValues) + { + return attribute == attributeName && this.attributeValues.SequenceEqual(attributeValues); } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeAnnotationBase.cs b/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeAnnotationBase.cs index 49d9ca1a40..f440c52795 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeAnnotationBase.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeAnnotationBase.cs @@ -1,5 +1,6 @@ using System.Collections.Generic; using System.Linq; +using Rubberduck.Common; using Rubberduck.Parsing.Grammar; using Rubberduck.VBEditor; @@ -7,14 +8,33 @@ namespace Rubberduck.Parsing.Annotations { public abstract class FlexibleAttributeAnnotationBase : AnnotationBase, IAttributeAnnotation { - protected FlexibleAttributeAnnotationBase(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IReadOnlyList parameters) - :base(qualifiedSelection, context) + protected FlexibleAttributeAnnotationBase(string name, AnnotationTarget target, bool allowMultiple = false) + : base(name, target, allowMultiple) + { } + + public IReadOnlyList AnnotationToAttributeValues(IReadOnlyList annotationValues) { - Attribute = parameters?.FirstOrDefault() ?? string.Empty; - AttributeValues = parameters?.Skip(1).ToList() ?? new List(); + // skip the attribute specification, which is taken from the annotationValues + // also we MUST NOT adjust quotation of annotationValues here + return annotationValues?.Skip(1).ToList(); } - public string Attribute { get; } - public IReadOnlyList AttributeValues { get; } + public string Attribute(IReadOnlyList annotationValues) + { + // The Attribute name is NEVER quoted, therefore unquote here + return annotationValues.FirstOrDefault()?.UnQuote() ?? ""; + } + + public IReadOnlyList AttributeToAnnotationValues(IReadOnlyList attributeValues) + { + // Must not adjust quotation status + return attributeValues; + } + + public bool MatchesAttributeDefinition(string attributeName, IReadOnlyList attributeValues) + { + // Implementers are the fallback. They must not return true here to avoid locking out more suitable candidates + return false; + } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeValueAnnotationBase.cs b/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeValueAnnotationBase.cs index 1a8d5e3bc8..4750032bf7 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeValueAnnotationBase.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeValueAnnotationBase.cs @@ -1,6 +1,7 @@ using System; using System.Collections.Generic; using System.Linq; +using Rubberduck.Common; using Rubberduck.Parsing.Grammar; using Rubberduck.VBEditor; @@ -9,28 +10,34 @@ namespace Rubberduck.Parsing.Annotations public abstract class FlexibleAttributeValueAnnotationBase : AnnotationBase, IAttributeAnnotation { public string Attribute { get; } - public IReadOnlyList AttributeValues { get; } - protected FlexibleAttributeValueAnnotationBase(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable attributeValues) - :base(qualifiedSelection, context) + private readonly int _numberOfValues; + + protected FlexibleAttributeValueAnnotationBase(string name, AnnotationTarget target, string attribute, int numberOfValues) + : base(name, target) + { + Attribute = attribute; + _numberOfValues = numberOfValues; + } + + public bool MatchesAttributeDefinition(string attributeName, IReadOnlyList attributeValues) { - var flexibleAttributeValueInfo = FlexibleAttributeValueInfo(GetType()); + return Attribute == attributeName && _numberOfValues == attributeValues.Count; + } - Attribute = flexibleAttributeValueInfo.attribute; - AttributeValues = attributeValues?.Take(flexibleAttributeValueInfo.numberOfValues).ToList() ?? new List(); + public virtual IReadOnlyList AnnotationToAttributeValues(IReadOnlyList annotationValues) + { + return annotationValues.Take(_numberOfValues).Select(v => v.EnQuote()).ToList(); } - private static (string attribute, int numberOfValues) FlexibleAttributeValueInfo(Type annotationType) + public virtual IReadOnlyList AttributeToAnnotationValues(IReadOnlyList attributeValues) { - var attributeValueInfo = annotationType.GetCustomAttributes(false) - .OfType() - .SingleOrDefault(); + return attributeValues.Take(_numberOfValues).Select(v => v.EnQuote()).ToList(); + } - if (attributeValueInfo == null) - { - return ("", 0); - } - return (attributeValueInfo.AttributeName, attributeValueInfo.NumberOfParameters); + string IAttributeAnnotation.Attribute(IReadOnlyList annotationValues) + { + return Attribute; } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/FolderAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/FolderAnnotation.cs index b11a512f2b..85bcc0c611 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/FolderAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/FolderAnnotation.cs @@ -8,20 +8,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for specifying the Code Explorer folder a appears under. /// - [Annotation("Folder", AnnotationTarget.Module)] public sealed class FolderAnnotation : AnnotationBase { - public FolderAnnotation( - QualifiedSelection qualifiedSelection, - VBAParser.AnnotationContext context, - IEnumerable parameters) - : base(qualifiedSelection, context) - { - FolderName = parameters.FirstOrDefault() ?? string.Empty; - } - - public string FolderName { get; } - - public override string ToString() => $"Folder: {FolderName}"; + public FolderAnnotation() + : base("Folder", AnnotationTarget.Module) + { } } } diff --git a/Rubberduck.Parsing/Annotations/Implementations/IgnoreAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/IgnoreAnnotation.cs index c4972dd371..bacb9cf0e8 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/IgnoreAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/IgnoreAnnotation.cs @@ -8,28 +8,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for ignoring specific inspection results from a specified set of inspections. /// - [Annotation("Ignore", AnnotationTarget.General, true)] public sealed class IgnoreAnnotation : AnnotationBase { - public IgnoreAnnotation( - QualifiedSelection qualifiedSelection, - VBAParser.AnnotationContext context, - IEnumerable parameters) - : base(qualifiedSelection, context) - { - InspectionNames = parameters; - } - - public IEnumerable InspectionNames { get; } - - public bool IsIgnored(string inspectionName) - { - return InspectionNames.Contains(inspectionName); - } - - public override string ToString() - { - return $"Ignored inspections: {string.Join(", ", InspectionNames)}"; - } + public IgnoreAnnotation() + : base("Ignore", AnnotationTarget.General, true) + { } } } diff --git a/Rubberduck.Parsing/Annotations/Implementations/IgnoreModuleAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/IgnoreModuleAnnotation.cs index 670e49af2c..7a73829931 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/IgnoreModuleAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/IgnoreModuleAnnotation.cs @@ -8,25 +8,10 @@ namespace Rubberduck.Parsing.Annotations /// /// This annotation allows ignoring inspection results of defined inspections for a whole module /// - [Annotation("IgnoreModule", AnnotationTarget.Module, true)] public sealed class IgnoreModuleAnnotation : AnnotationBase { - public IgnoreModuleAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(qualifiedSelection, context) - { - InspectionNames = parameters; - } - - public IEnumerable InspectionNames { get; } - - public bool IsIgnored(string inspectionName) - { - return !InspectionNames.Any() || InspectionNames.Contains(inspectionName); - } - - public override string ToString() - { - return $"Ignored inspections: {string.Join(", ", InspectionNames)}"; - } + public IgnoreModuleAnnotation() + : base("IgnoreModule", AnnotationTarget.Module, true) + { } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/IgnoreTestAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/IgnoreTestAnnotation.cs index f3792d7ba9..747e1a73af 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/IgnoreTestAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/IgnoreTestAnnotation.cs @@ -7,12 +7,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Used to indicate the test engine that a unit test is to be ignored. /// - [Annotation("IgnoreTest", AnnotationTarget.Member)] public sealed class IgnoreTestAnnotation : AnnotationBase { - public IgnoreTestAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(qualifiedSelection, context) - { - } + public IgnoreTestAnnotation() + : base("IgnoreTest", AnnotationTarget.Member) + { } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/InterfaceAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/InterfaceAnnotation.cs index b9c020cbc6..b8d7fbedda 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/InterfaceAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/InterfaceAnnotation.cs @@ -7,12 +7,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Used to mark a class module as an interface, so that Rubberduck treats it as such even if it's not implemented in any opened project. /// - [Annotation("Interface", AnnotationTarget.Module)] public sealed class InterfaceAnnotation : AnnotationBase { - public InterfaceAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(qualifiedSelection, context) - { - } + public InterfaceAnnotation() + : base("Interface", AnnotationTarget.Module) + { } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/MemberAttributeAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/MemberAttributeAnnotation.cs index d1b88de08a..725646c3f3 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/MemberAttributeAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/MemberAttributeAnnotation.cs @@ -11,13 +11,10 @@ namespace Rubberduck.Parsing.Annotations /// It is disjoint from ModuleAttributeAnnotation because of annotation scoping shenanigans. /// // marked as Variable annotation to accomodate annotations of constants - // FIXME consider whether type hierarchy is sufficient to mark as Attribute annotation - // FIXME considre whether this annotation (and ModuleAttribute) should be allowed multiple times - [Annotation("MemberAttribute", AnnotationTarget.Member | AnnotationTarget.Variable)] public class MemberAttributeAnnotation : FlexibleAttributeAnnotationBase { - public MemberAttributeAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IReadOnlyList parameters) - :base(qualifiedSelection, context, parameters) + public MemberAttributeAnnotation() + : base("MemberAttribute", AnnotationTarget.Member | AnnotationTarget.Variable) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/ModuleAttributeAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ModuleAttributeAnnotation.cs index 75977efcdc..55b44a5397 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/ModuleAttributeAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/ModuleAttributeAnnotation.cs @@ -7,12 +7,10 @@ namespace Rubberduck.Parsing.Annotations /// /// This annotation allows specifying arbitrary VB_Attribute entries. /// - // FIXME Consider whether the type-hierarchy alone is sufficient to mark this as an Attribute-Annotation - [Annotation("ModuleAttribute", AnnotationTarget.Module)] public class ModuleAttributeAnnotation : FlexibleAttributeAnnotationBase { - public ModuleAttributeAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IReadOnlyList parameters) - :base(qualifiedSelection, context, parameters) + public ModuleAttributeAnnotation() + : base("ModuleAttribute", AnnotationTarget.Module) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/ModuleCleanupAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ModuleCleanupAnnotation.cs index 8f121d3770..4c04e6d314 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/ModuleCleanupAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/ModuleCleanupAnnotation.cs @@ -7,15 +7,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Marks a method that the test engine will execute after all unit tests in a test module have executed. /// - [Annotation("ModuleCleanup", AnnotationTarget.Member)] public sealed class ModuleCleanupAnnotation : AnnotationBase { - public ModuleCleanupAnnotation( - QualifiedSelection qualifiedSelection, - VBAParser.AnnotationContext context, - IEnumerable parameters) - : base(qualifiedSelection, context) - { - } + public ModuleCleanupAnnotation() + : base("ModuleCleanup", AnnotationTarget.Member) + { } } } diff --git a/Rubberduck.Parsing/Annotations/Implementations/ModuleDescriptionAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ModuleDescriptionAnnotation.cs index 74c02de61b..d44c0702ca 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/ModuleDescriptionAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/ModuleDescriptionAnnotation.cs @@ -10,12 +10,10 @@ namespace Rubberduck.Parsing.Annotations /// /// This is a class distinct from Member and Variable descriptions, because annotation scoping is annoyingly complicated and Rubberduck has a much easier time if module annotations and member annotations don't have the same name. /// - [Annotation("ModuleDescription", AnnotationTarget.Module)] - [FlexibleAttributeValueAnnotation("VB_Description", 1)] public sealed class ModuleDescriptionAnnotation : DescriptionAttributeAnnotationBase { - public ModuleDescriptionAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(qualifiedSelection, context, parameters) + public ModuleDescriptionAnnotation() + : base("ModuleDescription", AnnotationTarget.Module, "VB_Description", 1) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/ModuleInitializeAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ModuleInitializeAnnotation.cs index f37fc7aedc..a6254bff3b 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/ModuleInitializeAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/ModuleInitializeAnnotation.cs @@ -7,15 +7,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Marks a method that the test engine will execute before executing the first unit test in a test module. /// - [Annotation("ModuleInitialize", AnnotationTarget.Member)] public sealed class ModuleInitializeAnnotation : AnnotationBase { - public ModuleInitializeAnnotation( - QualifiedSelection qualifiedSelection, - VBAParser.AnnotationContext context, - IEnumerable parameters) - : base(qualifiedSelection, context) - { - } + public ModuleInitializeAnnotation() + : base("ModuleInitialize", AnnotationTarget.Member) + { } } } diff --git a/Rubberduck.Parsing/Annotations/Implementations/NoIndentAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/NoIndentAnnotation.cs index e788e44ea5..43fd926ebd 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/NoIndentAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/NoIndentAnnotation.cs @@ -7,12 +7,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Marks a module that Smart Indenter ignores. /// - [Annotation("NoIndent", AnnotationTarget.Module)] public sealed class NoIndentAnnotation : AnnotationBase { - public NoIndentAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(qualifiedSelection, context) - { - } + public NoIndentAnnotation() + : base("NoIndent", AnnotationTarget.Module) + { } } } diff --git a/Rubberduck.Parsing/Annotations/Implementations/NotRecognizedAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/NotRecognizedAnnotation.cs index c271b9c0b5..8c5e12d81f 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/NotRecognizedAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/NotRecognizedAnnotation.cs @@ -8,14 +8,10 @@ namespace Rubberduck.Parsing.Annotations /// Used for all annotations not recognized by RD. /// Since this is not actually an annotation, it has no valid target /// - [Annotation("NotRecognized", 0)] public sealed class NotRecognizedAnnotation : AnnotationBase { - public NotRecognizedAnnotation( - QualifiedSelection qualifiedSelection, - VBAParser.AnnotationContext context, - IEnumerable parameters) - : base(qualifiedSelection, context) - {} + public NotRecognizedAnnotation() + : base("NotRecognized", 0) + { } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/ObsoleteAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/ObsoleteAnnotation.cs index bddea5220f..d7112303c3 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/ObsoleteAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/ObsoleteAnnotation.cs @@ -8,17 +8,14 @@ namespace Rubberduck.Parsing.Annotations /// /// Used to mark members as obsolete, so that Rubberduck can warn users whenever they try to use an obsolete member. /// - [Annotation("Obsolete", AnnotationTarget.Member | AnnotationTarget.Variable)] public sealed class ObsoleteAnnotation : AnnotationBase { public string ReplacementDocumentation { get; } - public ObsoleteAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(qualifiedSelection, context) - { - var firstParameter = parameters.FirstOrDefault(); + public ObsoleteAnnotation() + : base("Obsolete", AnnotationTarget.Member | AnnotationTarget.Variable) + { } - ReplacementDocumentation = string.IsNullOrWhiteSpace(firstParameter) ? "" : firstParameter; - } + // FIXME correctly handle the fact that the replacement documentation is only the first parameter! } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/PredeclaredIdAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/PredeclaredIdAnnotation.cs index f4e5c247eb..4216718479 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/PredeclaredIdAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/PredeclaredIdAnnotation.cs @@ -7,12 +7,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Used for specifying a module's VB_PredeclaredId attribute. /// - [Annotation("PredeclaredId", AnnotationTarget.Module)] - [FixedAttributeValueAnnotation("VB_PredeclaredId", "True")] public sealed class PredeclaredIdAnnotation : FixedAttributeValueAnnotationBase { - public PredeclaredIdAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(qualifiedSelection, context) + public PredeclaredIdAnnotation() + : base("PredeclaredId", AnnotationTarget.Module, "VB_PredeclaredId", new[] { "True" }) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/TestCleanupAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/TestCleanupAnnotation.cs index bfe69a5821..069280d0b5 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/TestCleanupAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/TestCleanupAnnotation.cs @@ -7,14 +7,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Marks a method that the test engine will execute after executing each unit test in a test module. /// - [Annotation("TestCleanup", AnnotationTarget.Member)] public sealed class TestCleanupAnnotation : AnnotationBase { - public TestCleanupAnnotation( - QualifiedSelection qualifiedSelection, - VBAParser.AnnotationContext context, - IEnumerable parameters) - : base(qualifiedSelection, context) + public TestCleanupAnnotation() + : base("TestCleanup", AnnotationTarget.Member) { } } diff --git a/Rubberduck.Parsing/Annotations/Implementations/TestInitializeAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/TestInitializeAnnotation.cs index 507d62b937..ed273930e6 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/TestInitializeAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/TestInitializeAnnotation.cs @@ -7,15 +7,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Marks a method that the test engine will execute before executing each unit test in a test module. /// - [Annotation("TestInitialize", AnnotationTarget.Member)] public sealed class TestInitializeAnnotation : AnnotationBase { - public TestInitializeAnnotation( - QualifiedSelection qualifiedSelection, - VBAParser.AnnotationContext context, - IEnumerable parameters) - : base(qualifiedSelection, context) - { - } + public TestInitializeAnnotation() + : base("TestInitialize", AnnotationTarget.Member) + { } } } diff --git a/Rubberduck.Parsing/Annotations/Implementations/TestMethodAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/TestMethodAnnotation.cs index 3fc04a8715..42c6538124 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/TestMethodAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/TestMethodAnnotation.cs @@ -9,27 +9,21 @@ namespace Rubberduck.Parsing.Annotations /// /// Marks a method that the test engine will execute as a unit test. /// - [Annotation("TestMethod", AnnotationTarget.Member)] public sealed class TestMethodAnnotation : AnnotationBase { - public TestMethodAnnotation( - QualifiedSelection qualifiedSelection, - VBAParser.AnnotationContext context, - IEnumerable parameters) - : base(qualifiedSelection, context) + public TestMethodAnnotation() + : base("TestMethod", AnnotationTarget.Member) { // FIXME unify handling of quoted arguments to annotations. - // That should probably be part of VBAParserAnnotationFactory's handling of the annotationArguments context - var firstParameter = parameters.FirstOrDefault(); - if ((firstParameter?.StartsWith("\"") ?? false) && firstParameter.EndsWith("\"")) - { - // Strip surrounding double quotes - firstParameter = firstParameter.Substring(1, firstParameter.Length - 2); - } + //// That should probably be part of VBAParserAnnotationFactory's handling of the annotationArguments context + //var firstParameter = parameters.FirstOrDefault(); + //if ((firstParameter?.StartsWith("\"") ?? false) && firstParameter.EndsWith("\"")) + //{ + // // Strip surrounding double quotes + // firstParameter = firstParameter.Substring(1, firstParameter.Length - 2); + //} - Category = string.IsNullOrWhiteSpace(firstParameter) ? string.Empty : firstParameter; + //Category = string.IsNullOrWhiteSpace(firstParameter) ? string.Empty : firstParameter; } - - public string Category { get; } } } diff --git a/Rubberduck.Parsing/Annotations/Implementations/TestModuleAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/TestModuleAnnotation.cs index 6d34b5d8c6..4faa351d8a 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/TestModuleAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/TestModuleAnnotation.cs @@ -10,16 +10,10 @@ namespace Rubberduck.Parsing.Annotations /// /// Unit test discovery only inspects modules with a @TestModule annotation. /// - [Annotation("TestModule", AnnotationTarget.Module)] public sealed class TestModuleAnnotation : AnnotationBase { - // TODO investigate unused parameters argument. Possibly needed to match signature for construction through VBAParserAnnotationFactory?! - public TestModuleAnnotation( - QualifiedSelection qualifiedSelection, - VBAParser.AnnotationContext context, - IEnumerable parameters) - : base(qualifiedSelection, context) - { - } + public TestModuleAnnotation() + : base("TestModule", AnnotationTarget.Module) + { } } } diff --git a/Rubberduck.Parsing/Annotations/Implementations/VariableDescriptionAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/VariableDescriptionAnnotation.cs index ac3397023c..7d4297dff6 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/VariableDescriptionAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Implementations/VariableDescriptionAnnotation.cs @@ -4,12 +4,10 @@ namespace Rubberduck.Parsing.Annotations { - [Annotation("VariableDescription", AnnotationTarget.Variable)] - [FlexibleAttributeValueAnnotation("VB_VarDescription", 1)] public class VariableDescriptionAnnotation : DescriptionAttributeAnnotationBase - { - public VariableDescriptionAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable parameters) - : base(qualifiedSelection, context, parameters) + { + public VariableDescriptionAnnotation() + : base("VariableDescription", AnnotationTarget.Variable, "VB_VarDescription", 1) {} } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/InvalidAnnotationArgumentException.cs b/Rubberduck.Parsing/Annotations/InvalidAnnotationArgumentException.cs index 2e0ad2315c..06b4706e92 100644 --- a/Rubberduck.Parsing/Annotations/InvalidAnnotationArgumentException.cs +++ b/Rubberduck.Parsing/Annotations/InvalidAnnotationArgumentException.cs @@ -7,7 +7,6 @@ public class InvalidAnnotationArgumentException : Exception { public InvalidAnnotationArgumentException(string message) : base(message) - { - } + { } } } diff --git a/Rubberduck.Parsing/Annotations/ParseTreeAnnotation.cs b/Rubberduck.Parsing/Annotations/ParseTreeAnnotation.cs new file mode 100644 index 0000000000..5e3afe9d12 --- /dev/null +++ b/Rubberduck.Parsing/Annotations/ParseTreeAnnotation.cs @@ -0,0 +1,81 @@ +using Rubberduck.Parsing.Grammar; +using Rubberduck.VBEditor; +using System; +using System.Collections.Generic; +using System.Linq; +using System.Text; +using System.Threading.Tasks; + +namespace Rubberduck.Parsing.Annotations +{ + public class ParseTreeAnnotation + { + public const string ANNOTATION_MARKER = "@"; + + private readonly Lazy _annotatedLine; + + internal ParseTreeAnnotation(IAnnotation annotation, QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context) + { + QualifiedSelection = qualifiedSelection; + Context = context; + Annotation = annotation; + _annotatedLine = new Lazy(GetAnnotatedLine); + AnnotationArguments = AnnotationParametersFromContext(Context); + } + + // FIXME annotation constructor for unit-testing purposes alone! + internal ParseTreeAnnotation(IAnnotation annotation, QualifiedSelection qualifiedSelection, IEnumerable arguments) + { + Annotation = annotation; + QualifiedSelection = qualifiedSelection; + _annotatedLine = new Lazy(() => null); + Context = null; + AnnotationArguments = arguments.ToList(); + } + + // needs to be accessible to IllegalAnnotationInspection + public QualifiedSelection QualifiedSelection { get; } + public VBAParser.AnnotationContext Context { get; } + public int? AnnotatedLine => _annotatedLine.Value; + + // needs to be accessible to all external consumers + public IAnnotation Annotation { get; } + public IReadOnlyList AnnotationArguments { get; } + + private static List AnnotationParametersFromContext(VBAParser.AnnotationContext context) + { + var parameters = new List(); + var argList = context?.annotationArgList(); + if (argList != null) + { + // CAUTION! THIS MUST NOT ADJUST THE QUOTING BEHAVIOUR! + // the reason for that is the different quoting requirements for attributes. + // some attributes require quoted values, some require unquoted values. + // we currently don't have a mechanism to specify which needs which + parameters.AddRange(argList.annotationArg().Select(arg => arg.GetText())); + } + return parameters; + } + + private int? GetAnnotatedLine() + { + var enclosingEndOfStatement = Context.GetAncestor(); + + //Annotations on the same line as non-whitespace statements do not scope to anything. + if (enclosingEndOfStatement.Start.TokenIndex != 0) + { + var firstEndOfLine = enclosingEndOfStatement.GetFirstEndOfLine(); + var parentEndOfLine = Context.GetAncestor(); + if (firstEndOfLine.Equals(parentEndOfLine)) + { + return null; + } + } + + var lastToken = enclosingEndOfStatement.stop; + return lastToken.Type == VBAParser.NEWLINE + ? lastToken.Line + 1 + : lastToken.Line; + } + } +} diff --git a/Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs b/Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs index 13d104cc85..34295eb40f 100644 --- a/Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs +++ b/Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs @@ -8,47 +8,29 @@ namespace Rubberduck.Parsing.Annotations { public sealed class VBAParserAnnotationFactory : IAnnotationFactory { - private readonly Dictionary _creators = new Dictionary(); + private readonly Dictionary _lookup = new Dictionary(); + private readonly IAnnotation unrecognized; - public VBAParserAnnotationFactory(IEnumerable recognizedAnnotationTypes) + public VBAParserAnnotationFactory(IEnumerable recognizedAnnotations) { - foreach (var annotationType in recognizedAnnotationTypes) + foreach (var annotation in recognizedAnnotations) { - // Extract the static information about the annotation type from it's AnnotationAttribute - var staticInfo = annotationType.GetCustomAttributes(false) - .OfType() - .Single(); - _creators.Add(staticInfo.Name.ToUpperInvariant(), annotationType); + if (annotation is NotRecognizedAnnotation) + { + unrecognized = annotation; + } + _lookup.Add(annotation.Name.ToUpperInvariant(), annotation); } } - public IAnnotation Create(VBAParser.AnnotationContext context, QualifiedSelection qualifiedSelection) + public ParseTreeAnnotation Create(VBAParser.AnnotationContext context, QualifiedSelection qualifiedSelection) { var annotationName = context.annotationName().GetText(); - var parameters = AnnotationParametersFromContext(context); - return CreateAnnotation(annotationName, parameters, qualifiedSelection, context); - } - - private static List AnnotationParametersFromContext(VBAParser.AnnotationContext context) - { - var parameters = new List(); - var argList = context.annotationArgList(); - if (argList != null) + if (_lookup.TryGetValue(annotationName.ToUpperInvariant(), out var annotation)) { - parameters.AddRange(argList.annotationArg().Select(arg => arg.GetText())); + return new ParseTreeAnnotation(annotation, qualifiedSelection, context); } - return parameters; - } - - private IAnnotation CreateAnnotation(string annotationName, IReadOnlyList parameters, - QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context) - { - if (_creators.TryGetValue(annotationName.ToUpperInvariant(), out var annotationClrType)) - { - return (IAnnotation) Activator.CreateInstance(annotationClrType, qualifiedSelection, context, parameters); - } - - return new NotRecognizedAnnotation(qualifiedSelection, context, parameters); + return new ParseTreeAnnotation(unrecognized, qualifiedSelection, context); } } } diff --git a/Rubberduck.Parsing/Symbols/Attributes.cs b/Rubberduck.Parsing/Symbols/Attributes.cs index f87cefd737..46628a79ce 100644 --- a/Rubberduck.Parsing/Symbols/Attributes.cs +++ b/Rubberduck.Parsing/Symbols/Attributes.cs @@ -123,27 +123,27 @@ public static string MemberAttributeName(string attributeBaseName, string member return $"{memberName}.{attributeBaseName}"; } - public bool HasAttributeFor(IAttributeAnnotation annotation, string memberName = null) + public bool HasAttributeFor(ParseTreeAnnotation annotation, string memberName = null) { return AttributeNodesFor(annotation, memberName).Any(); } - public IEnumerable AttributeNodesFor(IAttributeAnnotation annotation, string memberName = null) + public IEnumerable AttributeNodesFor(ParseTreeAnnotation annotation, string memberName = null) { - if (!annotation.GetType().GetInterfaces().Contains(typeof(IAttributeAnnotation))) + var attribute = annotation.Attribute(); + if (string.IsNullOrEmpty(attribute)) { return Enumerable.Empty(); } var attributeName = memberName != null - ? MemberAttributeName(annotation.Attribute, memberName) - : annotation.Attribute; - + ? MemberAttributeName(attribute, memberName) + : attribute; //VB_Ext_Key annotation depend on the defined key for identity. - if (annotation.Attribute.Equals("VB_Ext_Key", StringComparison.OrdinalIgnoreCase)) + if (attribute.Equals("VB_Ext_Key", StringComparison.OrdinalIgnoreCase)) { return this.Where(a => a.Name.Equals(attributeName, StringComparison.OrdinalIgnoreCase) - && a.Values[0] == annotation.AttributeValues[0]); + && a.Values[0] == annotation.AttributeValues()[0]); } return this.Where(a => a.Name.Equals(attributeName, StringComparison.OrdinalIgnoreCase)); diff --git a/Rubberduck.Parsing/Symbols/ClassModuleDeclaration.cs b/Rubberduck.Parsing/Symbols/ClassModuleDeclaration.cs index be90db1326..0dbf2bc86e 100644 --- a/Rubberduck.Parsing/Symbols/ClassModuleDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/ClassModuleDeclaration.cs @@ -24,7 +24,7 @@ public class ClassModuleDeclaration : ModuleDeclaration Declaration projectDeclaration, string name, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes, bool isWithEvents = false, bool hasDefaultInstanceVariable = false, @@ -62,7 +62,7 @@ public class ClassModuleDeclaration : ModuleDeclaration parent, coClass.Name, false, - new List(), + new List(), attributes, coClass.EventInterfaces.Any(), coClass.IsAppObject, @@ -86,7 +86,7 @@ public class ClassModuleDeclaration : ModuleDeclaration parent, @interface.Name, false, - new List(), + new List(), attributes) { } diff --git a/Rubberduck.Parsing/Symbols/Declaration.cs b/Rubberduck.Parsing/Symbols/Declaration.cs index 43f73a78d6..71f60987b0 100644 --- a/Rubberduck.Parsing/Symbols/Declaration.cs +++ b/Rubberduck.Parsing/Symbols/Declaration.cs @@ -37,7 +37,7 @@ public class Declaration : IEquatable bool isArray, VBAParser.AsTypeClauseContext asTypeContext, bool isUserDefined = true, - IEnumerable annotations = null, + IEnumerable annotations = null, Attributes attributes = null, bool undeclared = false) : this( @@ -76,7 +76,7 @@ public class Declaration : IEquatable bool isArray, VBAParser.AsTypeClauseContext asTypeContext, bool isUserDefined = true, - IEnumerable annotations = null, + IEnumerable annotations = null, Attributes attributes = null) : this( qualifiedName, @@ -114,7 +114,7 @@ public class Declaration : IEquatable bool isArray, VBAParser.AsTypeClauseContext asTypeContext, bool isUserDefined = true, - IEnumerable annotations = null, + IEnumerable annotations = null, Attributes attributes = null) { QualifiedName = qualifiedName; @@ -275,8 +275,8 @@ public static Declaration GetProjectParent(Declaration declaration) private ConcurrentDictionary _references = new ConcurrentDictionary(); public IEnumerable References => _references.Keys; - protected IEnumerable _annotations; - public IEnumerable Annotations => _annotations ?? new List(); + protected IEnumerable _annotations; + public IEnumerable Annotations => _annotations ?? new List(); private readonly Attributes _attributes; public Attributes Attributes => _attributes; @@ -359,7 +359,7 @@ private bool IsObjectOrObjectArray string identifier, Declaration callee, Selection selection, - IEnumerable annotations, + IEnumerable annotations, bool isAssignmentTarget = false, bool hasExplicitLetStatement = false, bool isSetAssigned = false, diff --git a/Rubberduck.Parsing/Symbols/DeclarationLoaders/AliasDeclarations.cs b/Rubberduck.Parsing/Symbols/DeclarationLoaders/AliasDeclarations.cs index d1fff19503..a1295e3fc0 100644 --- a/Rubberduck.Parsing/Symbols/DeclarationLoaders/AliasDeclarations.cs +++ b/Rubberduck.Parsing/Symbols/DeclarationLoaders/AliasDeclarations.cs @@ -148,7 +148,7 @@ private PropertyGetDeclaration DatePropertyGet() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -167,7 +167,7 @@ private PropertyGetDeclaration TimePropertyGet() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -220,7 +220,7 @@ private FunctionDeclaration ErrorFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -239,7 +239,7 @@ private FunctionDeclaration HexFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -258,7 +258,7 @@ private FunctionDeclaration OctFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -277,7 +277,7 @@ private FunctionDeclaration StrFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -296,7 +296,7 @@ private FunctionDeclaration StrConvFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -315,7 +315,7 @@ private FunctionDeclaration CurDirFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -334,7 +334,7 @@ private FunctionDeclaration CommandFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -353,7 +353,7 @@ private FunctionDeclaration EnvironFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -372,7 +372,7 @@ private FunctionDeclaration ChrFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -391,7 +391,7 @@ private FunctionDeclaration ChrBFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -410,7 +410,7 @@ private FunctionDeclaration ChrwFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -429,7 +429,7 @@ private FunctionDeclaration FormatFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -448,7 +448,7 @@ private FunctionDeclaration LCaseFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -467,7 +467,7 @@ private FunctionDeclaration LeftFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -486,7 +486,7 @@ private FunctionDeclaration LeftBFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -505,7 +505,7 @@ private FunctionDeclaration LTrimFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -524,7 +524,7 @@ private FunctionDeclaration MidFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -543,7 +543,7 @@ private FunctionDeclaration MidBFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -562,7 +562,7 @@ private FunctionDeclaration TrimFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -581,7 +581,7 @@ private FunctionDeclaration RightFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -600,7 +600,7 @@ private FunctionDeclaration RightBFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -619,7 +619,7 @@ private FunctionDeclaration RTrimFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -638,7 +638,7 @@ private FunctionDeclaration SpaceFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -657,7 +657,7 @@ private FunctionDeclaration StringFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -676,7 +676,7 @@ private FunctionDeclaration UCaseFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -695,7 +695,7 @@ private FunctionDeclaration InputFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -714,7 +714,7 @@ private FunctionDeclaration InputBFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } diff --git a/Rubberduck.Parsing/Symbols/DeclarationLoaders/DebugDeclarations.cs b/Rubberduck.Parsing/Symbols/DeclarationLoaders/DebugDeclarations.cs index 133271ed9f..ed294a8e01 100644 --- a/Rubberduck.Parsing/Symbols/DeclarationLoaders/DebugDeclarations.cs +++ b/Rubberduck.Parsing/Symbols/DeclarationLoaders/DebugDeclarations.cs @@ -81,7 +81,7 @@ private static ProceduralModuleDeclaration DebugModuleDeclaration(Declaration pa parentProject, "DebugModule", false, - new List(), + new List(), new Attributes()); } @@ -101,7 +101,7 @@ private static ClassModuleDeclaration DebugClassDeclaration(Declaration parentPr parentProject, "DebugClass", false, - new List(), + new List(), new Attributes(), true); } @@ -129,7 +129,7 @@ private static Declaration DebugObjectDeclaration(ProceduralModuleDeclaration de false, null, false, - new List(), + new List(), new Attributes()); } @@ -145,7 +145,7 @@ private static SubroutineDeclaration DebugAssertDeclaration(ClassModuleDeclarati null, Selection.Home, false, - new List(), + new List(), new Attributes()); } @@ -161,7 +161,7 @@ private static SubroutineDeclaration DebugPrintDeclaration(ClassModuleDeclaratio null, Selection.Home, false, - new List(), + new List(), new Attributes()); } } diff --git a/Rubberduck.Parsing/Symbols/DeclarationLoaders/FormEventDeclarations.cs b/Rubberduck.Parsing/Symbols/DeclarationLoaders/FormEventDeclarations.cs index fe7250b484..745b8d078d 100644 --- a/Rubberduck.Parsing/Symbols/DeclarationLoaders/FormEventDeclarations.cs +++ b/Rubberduck.Parsing/Symbols/DeclarationLoaders/FormEventDeclarations.cs @@ -94,7 +94,7 @@ private static Declaration UserFormActivateEvent(Declaration formsClassModule) false, null, false, - new List(), + new List(), new Attributes()); } @@ -113,7 +113,7 @@ private static Declaration UserFormDeactivateEvent(Declaration formsClassModule) false, null, false, - new List(), + new List(), new Attributes()); } @@ -132,7 +132,7 @@ private static Declaration UserFormInitializeEvent(Declaration formsClassModule) false, null, false, - new List(), + new List(), new Attributes()); } @@ -151,7 +151,7 @@ private static Declaration UserFormQueryCloseEvent(Declaration formsClassModule) false, null, false, - new List(), + new List(), new Attributes()); } @@ -194,7 +194,7 @@ private static Declaration UserFormResizeEvent(Declaration formsClassModule) false, null, false, - new List(), + new List(), new Attributes()); } @@ -213,7 +213,7 @@ private static Declaration UserFormTerminateEvent(Declaration formsClassModule) false, null, false, - new List(), + new List(), new Attributes()); } diff --git a/Rubberduck.Parsing/Symbols/DeclarationLoaders/SpecialFormDeclarations.cs b/Rubberduck.Parsing/Symbols/DeclarationLoaders/SpecialFormDeclarations.cs index 813f7b5a61..e30f97d641 100644 --- a/Rubberduck.Parsing/Symbols/DeclarationLoaders/SpecialFormDeclarations.cs +++ b/Rubberduck.Parsing/Symbols/DeclarationLoaders/SpecialFormDeclarations.cs @@ -94,7 +94,7 @@ private static FunctionDeclaration LBoundFunctionWithoutParameters(Declaration p Selection.Home, false, false, - new List(), + new List(), new Attributes()); } @@ -133,7 +133,7 @@ private static FunctionDeclaration UBoundFunctionWithoutParameters(Declaration p Selection.Home, false, false, - new List(), + new List(), new Attributes()); } } diff --git a/Rubberduck.Parsing/Symbols/DocumentModuleDeclaration.cs b/Rubberduck.Parsing/Symbols/DocumentModuleDeclaration.cs index 026974f8e7..371ffc4df6 100644 --- a/Rubberduck.Parsing/Symbols/DocumentModuleDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/DocumentModuleDeclaration.cs @@ -15,7 +15,7 @@ public class DocumentModuleDeclaration : ClassModuleDeclaration QualifiedMemberName qualifiedName, Declaration projectDeclaration, string name, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base(qualifiedName, projectDeclaration, diff --git a/Rubberduck.Parsing/Symbols/EventDeclaration.cs b/Rubberduck.Parsing/Symbols/EventDeclaration.cs index b6f82d0b20..a0548b6bda 100644 --- a/Rubberduck.Parsing/Symbols/EventDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/EventDeclaration.cs @@ -25,7 +25,7 @@ public sealed class EventDeclaration : Declaration, IParameterizedDeclaration Selection selection, bool isArray, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/ExternalProcedureDeclaration.cs b/Rubberduck.Parsing/Symbols/ExternalProcedureDeclaration.cs index 5f374be2b0..fc60e9f9ff 100644 --- a/Rubberduck.Parsing/Symbols/ExternalProcedureDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/ExternalProcedureDeclaration.cs @@ -22,7 +22,7 @@ public sealed class ExternalProcedureDeclaration : Declaration, IParameterizedDe ParserRuleContext context, Selection selection, bool isUserDefined, - IEnumerable annotations) + IEnumerable annotations) : base( name, parent, diff --git a/Rubberduck.Parsing/Symbols/FunctionDeclaration.cs b/Rubberduck.Parsing/Symbols/FunctionDeclaration.cs index 4de8a94e9c..f99a6878e4 100644 --- a/Rubberduck.Parsing/Symbols/FunctionDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/FunctionDeclaration.cs @@ -24,7 +24,7 @@ public sealed class FunctionDeclaration : ModuleBodyElementDeclaration Selection selection, bool isArray, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/IDeclarationFinderFactory.cs b/Rubberduck.Parsing/Symbols/IDeclarationFinderFactory.cs index 8a6786a615..489e26a9f5 100644 --- a/Rubberduck.Parsing/Symbols/IDeclarationFinderFactory.cs +++ b/Rubberduck.Parsing/Symbols/IDeclarationFinderFactory.cs @@ -10,7 +10,7 @@ public interface IDeclarationFinderFactory { DeclarationFinder Create( IReadOnlyList declarations, - IEnumerable annotations, + IEnumerable annotations, IReadOnlyList unresolvedMemberDeclarations, IReadOnlyDictionary> unboundDefaultMemberAccesses, IHostApplication hostApp); diff --git a/Rubberduck.Parsing/Symbols/IdentifierReference.cs b/Rubberduck.Parsing/Symbols/IdentifierReference.cs index 2baf0ab8d2..02d1e1f01b 100644 --- a/Rubberduck.Parsing/Symbols/IdentifierReference.cs +++ b/Rubberduck.Parsing/Symbols/IdentifierReference.cs @@ -22,7 +22,7 @@ public class IdentifierReference : IEquatable Declaration declaration, bool isAssignmentTarget = false, bool hasExplicitLetStatement = false, - IEnumerable annotations = null, + IEnumerable annotations = null, bool isSetAssigned = false, bool isIndexedDefaultMemberAccess = false, bool isNonIndexedDefaultMemberAccess = false, @@ -43,7 +43,7 @@ public class IdentifierReference : IEquatable IsNonIndexedDefaultMemberAccess = isNonIndexedDefaultMemberAccess; DefaultMemberRecursionDepth = defaultMemberRecursionDepth; IsArrayAccess = isArrayAccess; - Annotations = annotations ?? new List(); + Annotations = annotations ?? new List(); } public QualifiedModuleName QualifiedModuleName { get; } @@ -79,7 +79,7 @@ public class IdentifierReference : IEquatable public Declaration Declaration { get; } - public IEnumerable Annotations { get; } + public IEnumerable Annotations { get; } public bool HasExplicitLetStatement { get; } diff --git a/Rubberduck.Parsing/Symbols/ModuleBodyElementDeclaration.cs b/Rubberduck.Parsing/Symbols/ModuleBodyElementDeclaration.cs index a2037c1f08..650734b24e 100644 --- a/Rubberduck.Parsing/Symbols/ModuleBodyElementDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/ModuleBodyElementDeclaration.cs @@ -24,7 +24,7 @@ public abstract class ModuleBodyElementDeclaration : Declaration, IParameterized Selection selection, bool isArray, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/ModuleDeclaration.cs b/Rubberduck.Parsing/Symbols/ModuleDeclaration.cs index a3439a1198..bce18a86a6 100644 --- a/Rubberduck.Parsing/Symbols/ModuleDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/ModuleDeclaration.cs @@ -13,7 +13,7 @@ public abstract class ModuleDeclaration : Declaration string name, DeclarationType declarationType, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes, bool isWithEvents = false) : base( @@ -46,7 +46,7 @@ internal void AddMember(Declaration member) _members.Add(member); } - internal void RemoveAnnotations(ICollection annotationsToRemove) + internal void RemoveAnnotations(ICollection annotationsToRemove) { _annotations = _annotations?.Where(annotation => !annotationsToRemove.Contains(annotation)).ToList(); } @@ -55,7 +55,7 @@ internal void RemoveAnnotations(ICollection annotationsToRemove) private string FolderFromAnnotations() { - var @namespace = Annotations.OfType().FirstOrDefault(); + var @namespace = Annotations.Where(a => a.Annotation is FolderAnnotation).FirstOrDefault(); string result; if (@namespace == null) { @@ -65,8 +65,8 @@ private string FolderFromAnnotations() } else { - var value = @namespace.FolderName; - result = value; + var value = @namespace.AnnotationArguments.FirstOrDefault(); + result = value ?? ""; } return result; } diff --git a/Rubberduck.Parsing/Symbols/ProceduralModuleDeclaration.cs b/Rubberduck.Parsing/Symbols/ProceduralModuleDeclaration.cs index a29576ede1..21547e331e 100644 --- a/Rubberduck.Parsing/Symbols/ProceduralModuleDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/ProceduralModuleDeclaration.cs @@ -13,7 +13,7 @@ public sealed class ProceduralModuleDeclaration : ModuleDeclaration Declaration projectDeclaration, string name, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( qualifiedName, @@ -32,7 +32,7 @@ public sealed class ProceduralModuleDeclaration : ModuleDeclaration parent, statics.Name, false, - new List(), + new List(), attributes) { IsPrivateModule = statics.IsRestricted; @@ -45,7 +45,7 @@ public ProceduralModuleDeclaration(ComEnumeration pseudo, Declaration parent, Qu parent, $"_{pseudo.Name}", false, - new List(), + new List(), new Attributes()) { } public ProceduralModuleDeclaration(ComStruct pseudo, Declaration parent, QualifiedModuleName module) @@ -54,7 +54,7 @@ public ProceduralModuleDeclaration(ComStruct pseudo, Declaration parent, Qualifi parent, $"_{pseudo.Name}", false, - new List(), + new List(), new Attributes()) { } public bool IsPrivateModule { get; internal set; } diff --git a/Rubberduck.Parsing/Symbols/PropertyDeclaration.cs b/Rubberduck.Parsing/Symbols/PropertyDeclaration.cs index 052addc597..060272510e 100644 --- a/Rubberduck.Parsing/Symbols/PropertyDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/PropertyDeclaration.cs @@ -24,7 +24,7 @@ public abstract class PropertyDeclaration : ModuleBodyElementDeclaration Selection selection, bool isArray, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/PropertyGetDeclaration.cs b/Rubberduck.Parsing/Symbols/PropertyGetDeclaration.cs index d6b094870e..aab155674a 100644 --- a/Rubberduck.Parsing/Symbols/PropertyGetDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/PropertyGetDeclaration.cs @@ -23,7 +23,7 @@ public sealed class PropertyGetDeclaration : PropertyDeclaration Selection selection, bool isArray, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/PropertyLetDeclaration.cs b/Rubberduck.Parsing/Symbols/PropertyLetDeclaration.cs index a5c5d56855..a322b3cbc2 100644 --- a/Rubberduck.Parsing/Symbols/PropertyLetDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/PropertyLetDeclaration.cs @@ -21,7 +21,7 @@ public sealed class PropertyLetDeclaration : PropertyDeclaration ParserRuleContext attributesPassContext, Selection selection, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/PropertySetDeclaration.cs b/Rubberduck.Parsing/Symbols/PropertySetDeclaration.cs index 9f475e4d71..0a7450b6b4 100644 --- a/Rubberduck.Parsing/Symbols/PropertySetDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/PropertySetDeclaration.cs @@ -22,7 +22,7 @@ public sealed class PropertySetDeclaration : PropertyDeclaration ParserRuleContext attributesPassContext, Selection selection, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/SubroutineDeclaration.cs b/Rubberduck.Parsing/Symbols/SubroutineDeclaration.cs index febe82a296..2d0823c9a0 100644 --- a/Rubberduck.Parsing/Symbols/SubroutineDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/SubroutineDeclaration.cs @@ -21,7 +21,7 @@ public sealed class SubroutineDeclaration : ModuleBodyElementDeclaration ParserRuleContext attributesPassContext, Selection selection, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/UnboundMemberDeclaration.cs b/Rubberduck.Parsing/Symbols/UnboundMemberDeclaration.cs index 040e5fae5c..085b8a7f06 100644 --- a/Rubberduck.Parsing/Symbols/UnboundMemberDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/UnboundMemberDeclaration.cs @@ -16,7 +16,7 @@ public class UnboundMemberDeclaration : Declaration /// public ParserRuleContext CallingContext { get; private set; } - public UnboundMemberDeclaration(Declaration parentDeclaration, ParserRuleContext unboundIdentifier, ParserRuleContext callingContext, IEnumerable annotations) : + public UnboundMemberDeclaration(Declaration parentDeclaration, ParserRuleContext unboundIdentifier, ParserRuleContext callingContext, IEnumerable annotations) : base(new QualifiedMemberName(parentDeclaration.QualifiedName.QualifiedModuleName, unboundIdentifier.GetText()), parentDeclaration, parentDeclaration, diff --git a/Rubberduck.Parsing/Symbols/ValuedDeclaration.cs b/Rubberduck.Parsing/Symbols/ValuedDeclaration.cs index cf995da3ca..368f57b2d5 100644 --- a/Rubberduck.Parsing/Symbols/ValuedDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/ValuedDeclaration.cs @@ -17,7 +17,7 @@ public class ValuedDeclaration : Declaration string asTypeName, VBAParser.AsTypeClauseContext asTypeContext, string typeHint, - IEnumerable annotations, + IEnumerable annotations, Accessibility accessibility, DeclarationType declarationType, string value, diff --git a/Rubberduck.Parsing/Symbols/VariableDeclaration.cs b/Rubberduck.Parsing/Symbols/VariableDeclaration.cs index 6f4c6bfee5..d945a288c6 100644 --- a/Rubberduck.Parsing/Symbols/VariableDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/VariableDeclaration.cs @@ -23,7 +23,7 @@ public sealed class VariableDeclaration : Declaration, IInterfaceExposable Selection selection, bool isArray, VBAParser.AsTypeClauseContext asTypeContext, - IEnumerable annotations = null, + IEnumerable annotations = null, Attributes attributes = null) : base( qualifiedName, diff --git a/Rubberduck.Parsing/VBA/AnnotationUpdater.cs b/Rubberduck.Parsing/VBA/AnnotationUpdater.cs index 8c77a97e04..11e1a2f112 100644 --- a/Rubberduck.Parsing/VBA/AnnotationUpdater.cs +++ b/Rubberduck.Parsing/VBA/AnnotationUpdater.cs @@ -17,7 +17,7 @@ public class AnnotationUpdater : IAnnotationUpdater { private readonly Logger _logger = LogManager.GetCurrentClassLogger(); - public void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext context, AnnotationAttribute annotationInfo, IReadOnlyList values = null) + public void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext context, IAnnotation annotationInfo, IReadOnlyList values = null) { var annotationValues = values ?? new List(); @@ -68,14 +68,14 @@ public void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext conte rewriter.InsertAfter(previousEndOfLine.stop.TokenIndex, codeToAdd); } - private static string AnnotationText(AnnotationAttribute annotationInformation, IReadOnlyList values) + private static string AnnotationText(IAnnotation annotationInformation, IReadOnlyList values) { return AnnotationText(annotationInformation.Name, values); } private static string AnnotationText(string annotationType, IReadOnlyList values) { - return $"'{AnnotationBase.ANNOTATION_MARKER}{AnnotationBaseText(annotationType, values)}"; + return $"'{ParseTreeAnnotation.ANNOTATION_MARKER}{AnnotationBaseText(annotationType, values)}"; } private static string AnnotationBaseText(string annotationType, IReadOnlyList values) @@ -99,7 +99,7 @@ private static VBAParser.EndOfLineContext PreviousEndOfLine(ParserRuleContext co return previousEol; } - public void AddAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationAttribute annotationInfo, IReadOnlyList values = null) + public void AddAnnotation(IRewriteSession rewriteSession, Declaration declaration, IAnnotation annotationInfo, IReadOnlyList values = null) { var annotationValues = values ?? new List(); @@ -124,7 +124,7 @@ public void AddAnnotation(IRewriteSession rewriteSession, Declaration declaratio } } - private void AddModuleAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationAttribute annotationInfo, IReadOnlyList annotationValues) + private void AddModuleAnnotation(IRewriteSession rewriteSession, Declaration declaration, IAnnotation annotationInfo, IReadOnlyList annotationValues) { if (!annotationInfo.Target.HasFlag(AnnotationTarget.Module)) { @@ -146,7 +146,7 @@ private void AddModuleAnnotation(IRewriteSession rewriteSession, Declaration dec rewriter.InsertBefore(0, codeToAdd); } - private void AddVariableAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationAttribute annotationInfo, IReadOnlyList annotationValues) + private void AddVariableAnnotation(IRewriteSession rewriteSession, Declaration declaration, IAnnotation annotationInfo, IReadOnlyList annotationValues) { if (!annotationInfo.Target.HasFlag(AnnotationTarget.Variable)) { @@ -165,7 +165,7 @@ private void AddVariableAnnotation(IRewriteSession rewriteSession, Declaration d AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationInfo, annotationValues); } - private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationAttribute annotationInfo, IReadOnlyList annotationValues) + private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration declaration, IAnnotation annotationInfo, IReadOnlyList annotationValues) { if (!annotationInfo.Target.HasFlag(AnnotationTarget.Member)) { @@ -185,7 +185,7 @@ private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration dec } - public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, AnnotationAttribute annotationInfo, + public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, IAnnotation annotationInfo, IReadOnlyList values = null) { var annotationValues = values ?? new List(); @@ -214,7 +214,7 @@ private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration dec AddAnnotation(rewriteSession, new QualifiedContext(reference.QualifiedModuleName, reference.Context), annotationInfo, annotationValues); } - public void RemoveAnnotation(IRewriteSession rewriteSession, IAnnotation annotation) + public void RemoveAnnotation(IRewriteSession rewriteSession, ParseTreeAnnotation annotation) { if (annotation == null) { @@ -225,7 +225,7 @@ public void RemoveAnnotation(IRewriteSession rewriteSession, IAnnotation annotat if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode) { _logger.Warn($"Tried to remove an annotation with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})"); - _logger.Trace($"Tried to remove annotation {annotation.AnnotationType} at {annotation.QualifiedSelection.Selection} in module {annotation.QualifiedSelection.QualifiedName} using a rewriter not suitable for annotations."); + _logger.Trace($"Tried to remove annotation {annotation.Annotation.Name} at {annotation.QualifiedSelection.Selection} in module {annotation.QualifiedSelection.QualifiedName} using a rewriter not suitable for annotations."); return; } @@ -283,11 +283,11 @@ private static void RemoveEntireLine(IModuleRewriter rewriter, ParserRuleContext private static void RemoveAnnotationMarker(IModuleRewriter rewriter, VBAParser.AnnotationContext annotationContext) { var endOfAnnotationMarker = annotationContext.start.TokenIndex - 1; - var startOfAnnotationMarker = endOfAnnotationMarker - AnnotationBase.ANNOTATION_MARKER.Length + 1; + var startOfAnnotationMarker = endOfAnnotationMarker - ParseTreeAnnotation.ANNOTATION_MARKER.Length + 1; rewriter.RemoveRange(startOfAnnotationMarker, endOfAnnotationMarker); } - public void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable annotations) + public void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable annotations) { if (annotations == null) { @@ -330,7 +330,7 @@ public void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable newValues = null) + public void UpdateAnnotation(IRewriteSession rewriteSession, ParseTreeAnnotation annotation, IAnnotation annotationInfo, IReadOnlyList newValues = null) { var newAnnotationValues = newValues ?? new List(); @@ -344,15 +344,15 @@ public void UpdateAnnotation(IRewriteSession rewriteSession, IAnnotation annotat if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode) { _logger.Warn($"Tried to update an annotation with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})"); - _logger.Trace($"Tried to update annotation {annotation.AnnotationType} at {annotation.QualifiedSelection.Selection} in module {annotation.QualifiedSelection.QualifiedName} with annotation {annotationInfo.Name} with values {AnnotationValuesText(newAnnotationValues)} using a rewriter not suitable for annotations."); + _logger.Trace($"Tried to update annotation {annotation.Annotation.Name} at {annotation.QualifiedSelection.Selection} in module {annotation.QualifiedSelection.QualifiedName} with annotation {annotationInfo.Name} with values {AnnotationValuesText(newAnnotationValues)} using a rewriter not suitable for annotations."); return; } //If there are no common flags, the annotations cannot apply to the same target. - if ((annotation.MetaInformation.Target & annotationInfo.Target) == 0) + if ((annotation.Annotation.Target & annotationInfo.Target) == 0) { _logger.Warn("Tried to replace an annotation with an annotation without common flags."); - _logger.Trace($"Tried to replace an annotation {annotation.AnnotationType} with values {AnnotationValuesText(newValues)} at {annotation.QualifiedSelection.Selection} in module {annotation.QualifiedSelection.QualifiedName} with an annotation {annotationInfo.Name} with values {AnnotationValuesText(newAnnotationValues)}, which does not have any common flags."); + _logger.Trace($"Tried to replace an annotation {annotation.Annotation.Name} with values {AnnotationValuesText(newValues)} at {annotation.QualifiedSelection.Selection} in module {annotation.QualifiedSelection.QualifiedName} with an annotation {annotationInfo.Name} with values {AnnotationValuesText(newAnnotationValues)}, which does not have any common flags."); return; } diff --git a/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinder.cs b/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinder.cs index eb72f31ece..e013722309 100644 --- a/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinder.cs +++ b/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinder.cs @@ -11,10 +11,10 @@ namespace Rubberduck.Parsing.VBA.DeclarationCaching public class ConcurrentlyConstructedDeclarationFinder : DeclarationFinder { private const int _maxDegreeOfConstructionParallelism = -1; - + public ConcurrentlyConstructedDeclarationFinder( IReadOnlyList declarations, - IEnumerable annotations, + IEnumerable annotations, IReadOnlyList unresolvedMemberDeclarations, IReadOnlyDictionary> unboundDefaultMemberAccesses, IHostApplication hostApp = null) diff --git a/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinderFactory.cs b/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinderFactory.cs index 8dc8231d6e..0066923f09 100644 --- a/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinderFactory.cs +++ b/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinderFactory.cs @@ -10,7 +10,7 @@ public class ConcurrentlyConstructedDeclarationFinderFactory : IDeclarationFinde { public DeclarationFinder Create( IReadOnlyList declarations, - IEnumerable annotations, + IEnumerable annotations, IReadOnlyList unresolvedMemberDeclarations, IReadOnlyDictionary> unboundDefaultMemberAccesses, IHostApplication hostApp) diff --git a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs index 84d65b6127..2874269307 100644 --- a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs +++ b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs @@ -28,7 +28,7 @@ public class DeclarationFinder private readonly ConcurrentDictionary> _newUndeclared; private readonly ConcurrentBag _newUnresolved; private List _unresolved; - private IDictionary<(QualifiedModuleName module, int annotatedLine), List> _annotations; + private IDictionary<(QualifiedModuleName module, int annotatedLine), List> _annotations; private IDictionary> _parametersByParent; private IDictionary> _userDeclarationsByType; private IDictionary> _declarationsBySelection; @@ -64,10 +64,10 @@ private static QualifiedSelection GetGroupingKey(Declaration declaration) declaration.Context.GetSelection()) : declaration.QualifiedSelection; } - + public DeclarationFinder( IReadOnlyList declarations, - IEnumerable annotations, + IEnumerable annotations, IReadOnlyList unresolvedMemberDeclarations, IReadOnlyDictionary> unboundDefaultMemberAccesses, IHostApplication hostApp = null) @@ -91,7 +91,7 @@ protected virtual void ExecuteCollectionConstructionActions(List collect collectionConstructionActions.ForEach(action => action.Invoke()); } - private List CollectionConstructionActions(IReadOnlyList declarations, IEnumerable annotations, + private List CollectionConstructionActions(IReadOnlyList declarations, IEnumerable annotations, IReadOnlyList unresolvedMemberDeclarations) { var actions = new List @@ -543,17 +543,28 @@ public IEnumerable FindMemberMatches(Declaration parent, string mem : Enumerable.Empty(); } - public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine) + public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine) { return _annotations.TryGetValue((module, annotatedLine), out var result) ? result - : Enumerable.Empty(); + : Enumerable.Empty(); + } + + public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine, Type annotationType) + { + return FindAnnotations(module, annotatedLine).Where(pta => pta.Annotation.GetType() == annotationType); + } + + public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine) + where T : IAnnotation + { + return FindAnnotations(module, annotatedLine, typeof(T)); } - public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine, AnnotationTarget target) + public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine, AnnotationTarget target) { return FindAnnotations(module, annotatedLine) - .Where(annot => annot.MetaInformation.Target.HasFlag(target)); + .Where(annot => annot.Annotation.Target.HasFlag(target)); } public bool IsMatch(string declarationName, string potentialMatchName) diff --git a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinderFactory.cs b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinderFactory.cs index d357144e5d..21f92d2a17 100644 --- a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinderFactory.cs +++ b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinderFactory.cs @@ -9,7 +9,7 @@ namespace Rubberduck.Parsing.VBA.DeclarationCaching public class DeclarationFinderFactory : IDeclarationFinderFactory { public DeclarationFinder Create(IReadOnlyList declarations, - IEnumerable annotations, + IEnumerable annotations, IReadOnlyList unresolvedMemberDeclarations, IReadOnlyDictionary> unboundDefaultMemberAccesses, IHostApplication hostApp) diff --git a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs index d025eb3321..9aca286ca1 100644 --- a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs +++ b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs @@ -175,7 +175,7 @@ protected void ResolveDeclarations(QualifiedModuleName module, IParseTree tree, private ModuleDeclaration NewModuleDeclaration( QualifiedModuleName qualifiedModuleName, IParseTree tree, - IDictionary> annotationsOnWhiteSpaceLines, + IDictionary> annotationsOnWhiteSpaceLines, IDictionary<(string scopeIdentifier, DeclarationType scopeType),Attributes> attributes, Declaration projectDeclaration) { @@ -231,7 +231,7 @@ private static Attributes ModuleAttributes(QualifiedModuleName qualifiedModuleNa return moduleAttributes; } - private static IEnumerable FindModuleAnnotations(IParseTree tree, IDictionary> annotationsOnWhiteSpaceLines) + private static IEnumerable FindModuleAnnotations(IParseTree tree, IDictionary> annotationsOnWhiteSpaceLines) { if (annotationsOnWhiteSpaceLines == null) { @@ -244,14 +244,14 @@ private static IEnumerable FindModuleAnnotations(IParseTree tree, I if (firstModuleBodyLine == null) { return annotationsOnWhiteSpaceLines.Values.SelectMany(annotationList => annotationList) - .Where(annotation => annotation.MetaInformation.Target.HasFlag(AnnotationTarget.Module)); + .Where(annotation => annotation.Annotation.Target.HasFlag(AnnotationTarget.Module)); } var lastPossibleAnnotatedLine = firstModuleBodyLine.Value; var moduleAnnotations = annotationsOnWhiteSpaceLines.Keys .Where(line => (line <= lastPossibleAnnotatedLine)) .SelectMany(line => annotationsOnWhiteSpaceLines[line]) - .Where(annotation => annotation.MetaInformation.Target.HasFlag(AnnotationTarget.Module)); + .Where(annotation => annotation.Annotation.Target.HasFlag(AnnotationTarget.Module)); return moduleAnnotations; } diff --git a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs index bcd77812f3..209bd69d6d 100644 --- a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs +++ b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs @@ -18,7 +18,7 @@ public class DeclarationSymbolsListener : VBAParserBaseListener private Declaration _currentScopeDeclaration; private Declaration _parentDeclaration; - private readonly IDictionary> _annotations; + private readonly IDictionary> _annotations; private readonly IDictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes> _attributes; private readonly IDictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext> _membersAllowingAttributes; @@ -27,7 +27,7 @@ public class DeclarationSymbolsListener : VBAParserBaseListener public DeclarationSymbolsListener( Declaration moduleDeclaration, - IDictionary> annotations, + IDictionary> annotations, IDictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes> attributes, IDictionary<(string scopeIdentifier, DeclarationType scopeType), @@ -42,12 +42,12 @@ public class DeclarationSymbolsListener : VBAParserBaseListener SetCurrentScope(); } - private IEnumerable FindMemberAnnotations(int firstMemberLine) + private IEnumerable FindMemberAnnotations(int firstMemberLine) { return FindAnnotations(firstMemberLine, AnnotationTarget.Member); } - private IEnumerable FindAnnotations(int firstLine, AnnotationTarget requiredTarget) + private IEnumerable FindAnnotations(int firstLine, AnnotationTarget requiredTarget) { if (_annotations == null) { @@ -56,18 +56,18 @@ private IEnumerable FindAnnotations(int firstLine, AnnotationTarget if (_annotations.TryGetValue(firstLine, out var scopedAnnotations)) { - return scopedAnnotations.Where(annotation => annotation.MetaInformation.Target.HasFlag(requiredTarget)); + return scopedAnnotations.Where(annotation => annotation.Annotation.Target.HasFlag(requiredTarget)); } - return Enumerable.Empty(); + return Enumerable.Empty(); } - private IEnumerable FindVariableAnnotations(int firstVariableLine) + private IEnumerable FindVariableAnnotations(int firstVariableLine) { return FindAnnotations(firstVariableLine, AnnotationTarget.Variable); } - private IEnumerable FindGeneralAnnotations(int firstLine) + private IEnumerable FindGeneralAnnotations(int firstLine) { return FindAnnotations(firstLine, AnnotationTarget.General); } diff --git a/Rubberduck.Parsing/VBA/IAnnotationUpdater.cs b/Rubberduck.Parsing/VBA/IAnnotationUpdater.cs index 0c9e27dbb8..76fe8f5256 100644 --- a/Rubberduck.Parsing/VBA/IAnnotationUpdater.cs +++ b/Rubberduck.Parsing/VBA/IAnnotationUpdater.cs @@ -8,11 +8,11 @@ namespace Rubberduck.Parsing.VBA { public interface IAnnotationUpdater { - void AddAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationAttribute newAnnotation, IReadOnlyList values = null); - void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, AnnotationAttribute newAnnotation, IReadOnlyList values = null); - void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext context, AnnotationAttribute newAnnotation, IReadOnlyList values = null); - void RemoveAnnotation(IRewriteSession rewriteSession, IAnnotation annotation); - void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable annotations); - void UpdateAnnotation(IRewriteSession rewriteSession, IAnnotation oldAnnotation, AnnotationAttribute newAnnotation, IReadOnlyList newValues = null); + void AddAnnotation(IRewriteSession rewriteSession, Declaration declaration, IAnnotation newAnnotation, IReadOnlyList values = null); + void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, IAnnotation newAnnotation, IReadOnlyList values = null); + void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext context, IAnnotation newAnnotation, IReadOnlyList values = null); + void RemoveAnnotation(IRewriteSession rewriteSession, ParseTreeAnnotation annotation); + void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable annotations); + void UpdateAnnotation(IRewriteSession rewriteSession, ParseTreeAnnotation oldAnnotation, IAnnotation newAnnotation, IReadOnlyList newValues = null); } } \ No newline at end of file diff --git a/Rubberduck.Parsing/VBA/ModuleState.cs b/Rubberduck.Parsing/VBA/ModuleState.cs index 2c94180a97..5bcea77351 100644 --- a/Rubberduck.Parsing/VBA/ModuleState.cs +++ b/Rubberduck.Parsing/VBA/ModuleState.cs @@ -21,7 +21,7 @@ public class ModuleState public ParserState State { get; private set; } public int ModuleContentHashCode { get; private set; } public List Comments { get; private set; } - public List Annotations { get; private set; } + public List Annotations { get; private set; } public SyntaxErrorException ModuleException { get; private set; } public IDictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes> ModuleAttributes { get; private set; } public IDictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext> MembersAllowingAttributes { get; private set; } @@ -40,7 +40,7 @@ public ModuleState(ConcurrentDictionary declarations) ModuleContentHashCode = 0; Comments = new List(); - Annotations = new List(); + Annotations = new List(); ModuleException = null; ModuleAttributes = new Dictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes>(); MembersAllowingAttributes = new Dictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext>(); @@ -58,7 +58,7 @@ public ModuleState(ParserState state) State = state; ModuleContentHashCode = 0; Comments = new List(); - Annotations = new List(); + Annotations = new List(); ModuleException = null; ModuleAttributes = new Dictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes>(); MembersAllowingAttributes = new Dictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext>(); @@ -74,7 +74,7 @@ public ModuleState(SyntaxErrorException moduleException) State = ParserState.Error; ModuleContentHashCode = 0; Comments = new List(); - Annotations = new List(); + Annotations = new List(); ModuleException = moduleException; ModuleAttributes = new Dictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes>(); MembersAllowingAttributes = new Dictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext>(); @@ -123,7 +123,7 @@ public ModuleState SetComments(List comments) return this; } - public ModuleState SetAnnotations(List annotations) + public ModuleState SetAnnotations(List annotations) { Annotations = annotations; return this; diff --git a/Rubberduck.Parsing/VBA/Parsing/IModuleParser.cs b/Rubberduck.Parsing/VBA/Parsing/IModuleParser.cs index 493d35b7c9..33665b1806 100644 --- a/Rubberduck.Parsing/VBA/Parsing/IModuleParser.cs +++ b/Rubberduck.Parsing/VBA/Parsing/IModuleParser.cs @@ -14,7 +14,7 @@ namespace Rubberduck.Parsing.VBA.Parsing IParseTree codePaneParseTree, IParseTree attributesParseTree, IEnumerable comments, - IEnumerable annotations, + IEnumerable annotations, IDictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes> attributes, IDictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext> membersAllowingAttributes, ITokenStream codePaneTokenStream, @@ -34,7 +34,7 @@ ITokenStream attributesTokenStream public IParseTree CodePaneParseTree { get; } public IParseTree AttributesParseTree { get; } public IEnumerable Comments { get; } - public IEnumerable Annotations { get; } + public IEnumerable Annotations { get; } public IDictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes> Attributes { get; } public IDictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext> MembersAllowingAttributes { get; } public ITokenStream CodePaneTokenStream { get; } diff --git a/Rubberduck.Parsing/VBA/Parsing/ModuleParser.cs b/Rubberduck.Parsing/VBA/Parsing/ModuleParser.cs index f0d68f88bd..94966dc98c 100644 --- a/Rubberduck.Parsing/VBA/Parsing/ModuleParser.cs +++ b/Rubberduck.Parsing/VBA/Parsing/ModuleParser.cs @@ -119,7 +119,7 @@ private ModuleParseResults ParseInternal(QualifiedModuleName module, Cancellatio } - private (IEnumerable Comments, IEnumerable Annotations) CommentsAndAnnotations(QualifiedModuleName module, IParseTree tree) + private (IEnumerable Comments, IEnumerable Annotations) CommentsAndAnnotations(QualifiedModuleName module, IParseTree tree) { var commentListener = new CommentListener(); var annotationListener = new AnnotationListener(_annotationFactory, module); diff --git a/Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs b/Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs index 41c9667abc..3c4e977ab7 100644 --- a/Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs +++ b/Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs @@ -131,7 +131,7 @@ public BoundExpressionVisitor(DeclarationFinder declarationFinder) isSetAssignment); } - private IEnumerable FindIdentifierAnnotations(QualifiedModuleName module, int line) + private IEnumerable FindIdentifierAnnotations(QualifiedModuleName module, int line) { return _declarationFinder.FindAnnotations(module, line, AnnotationTarget.Identifier); } diff --git a/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs b/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs index e0f6808139..8efcc9b61a 100644 --- a/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs +++ b/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs @@ -160,10 +160,10 @@ private void ResolveLabel(ParserRuleContext context, string label) } } - private IEnumerable FindIdentifierAnnotations(QualifiedModuleName module, int line) + private IEnumerable FindIdentifierAnnotations(QualifiedModuleName module, int line) { return _declarationFinder.FindAnnotations(module, line) - .Where(annotation => annotation.MetaInformation.Target.HasFlag(AnnotationTarget.Identifier)); + .Where(annotation => annotation.Annotation.Target.HasFlag(AnnotationTarget.Identifier)); } private void ResolveDefault( diff --git a/Rubberduck.Parsing/VBA/RubberduckParserState.cs b/Rubberduck.Parsing/VBA/RubberduckParserState.cs index f6706cda72..d085817c0a 100644 --- a/Rubberduck.Parsing/VBA/RubberduckParserState.cs +++ b/Rubberduck.Parsing/VBA/RubberduckParserState.cs @@ -674,11 +674,11 @@ public IReadOnlyCollection GetModuleComments(QualifiedModuleName mo return moduleState.Comments; } - public List AllAnnotations + public List AllAnnotations { get { - var annotations = new List(); + var annotations = new List(); foreach (var state in _moduleStates.Values) { annotations.AddRange(state.Annotations); @@ -688,19 +688,19 @@ public List AllAnnotations } } - public IEnumerable GetModuleAnnotations(QualifiedModuleName module) + public IEnumerable GetModuleAnnotations(QualifiedModuleName module) { if (_moduleStates.TryGetValue(module, out var result)) { return result.Annotations; } - return Enumerable.Empty(); + return Enumerable.Empty(); } - public void SetModuleAnnotations(QualifiedModuleName module, IEnumerable annotations) + public void SetModuleAnnotations(QualifiedModuleName module, IEnumerable annotations) { - _moduleStates[module].SetAnnotations(new List(annotations)); + _moduleStates[module].SetAnnotations(new List(annotations)); } /// diff --git a/Rubberduck.UnitTesting/UnitTesting/TestDiscovery.cs b/Rubberduck.UnitTesting/UnitTesting/TestDiscovery.cs index f1d8701130..8584376f6b 100644 --- a/Rubberduck.UnitTesting/UnitTesting/TestDiscovery.cs +++ b/Rubberduck.UnitTesting/UnitTesting/TestDiscovery.cs @@ -37,7 +37,7 @@ public static bool IsTestMethod(RubberduckParserState state, Declaration item) { return !state.AllUserDeclarations.Any(d => d.DeclarationType == DeclarationType.Parameter && Equals(d.ParentScopeDeclaration, item)) && - item.Annotations.OfType().Any(); + item.Annotations.Any(pta => pta.Annotation is TestMethodAnnotation); } public static IEnumerable FindModuleInitializeMethods(QualifiedModuleName module, RubberduckParserState state) @@ -45,7 +45,7 @@ public static IEnumerable FindModuleInitializeMethods(QualifiedModu return GetTestModuleProcedures(state) .Where(m => m.QualifiedName.QualifiedModuleName == module && - m.Annotations.OfType().Any()); + m.Annotations.Any(pta => pta.Annotation is ModuleInitializeAnnotation)); } public static IEnumerable FindModuleCleanupMethods(QualifiedModuleName module, RubberduckParserState state) @@ -53,7 +53,7 @@ public static IEnumerable FindModuleCleanupMethods(QualifiedModuleN return GetTestModuleProcedures(state) .Where(m => m.QualifiedName.QualifiedModuleName == module && - m.Annotations.OfType().Any()); + m.Annotations.Any(pta => pta.Annotation is ModuleCleanupAnnotation)); } public static IEnumerable FindTestInitializeMethods(QualifiedModuleName module, RubberduckParserState state) @@ -61,7 +61,7 @@ public static IEnumerable FindTestInitializeMethods(QualifiedModule return GetTestModuleProcedures(state) .Where(m => m.QualifiedName.QualifiedModuleName == module && - m.Annotations.OfType().Any()); + m.Annotations.Any(pta => pta.Annotation is TestInitializeAnnotation)); } public static IEnumerable FindTestCleanupMethods(QualifiedModuleName module, RubberduckParserState state) @@ -69,7 +69,7 @@ public static IEnumerable FindTestCleanupMethods(QualifiedModuleNam return GetTestModuleProcedures(state) .Where(m => m.QualifiedName.QualifiedModuleName == module && - m.Annotations.OfType().Any()); + m.Annotations.Any(pta => pta.Annotation is TestCleanupAnnotation)); } private static IEnumerable GetTestModuleProcedures(RubberduckParserState state) @@ -78,14 +78,14 @@ private static IEnumerable GetTestModuleProcedures(RubberduckParser return procedures.Where(item => item.ParentDeclaration.DeclarationType == DeclarationType.ProceduralModule && - item.ParentDeclaration.Annotations.OfType().Any()); + item.ParentDeclaration.Annotations.Any(pta => pta.Annotation is TestModuleAnnotation)); } public static IEnumerable GetTestModules(this RubberduckParserState state) { return state.AllUserDeclarations.Where(item => item.DeclarationType == DeclarationType.ProceduralModule && - item.Annotations.OfType().Any()); + item.Annotations.Any(pta => pta.Annotation is TestModuleAnnotation)); } } } \ No newline at end of file diff --git a/Rubberduck.UnitTesting/UnitTesting/TestMethod.cs b/Rubberduck.UnitTesting/UnitTesting/TestMethod.cs index e886bf5f0d..3138d74597 100644 --- a/Rubberduck.UnitTesting/UnitTesting/TestMethod.cs +++ b/Rubberduck.UnitTesting/UnitTesting/TestMethod.cs @@ -6,6 +6,7 @@ using Rubberduck.VBEditor; using Rubberduck.Interaction.Navigation; using Rubberduck.Resources.UnitTesting; +using Rubberduck.Common; namespace Rubberduck.UnitTesting { @@ -24,9 +25,12 @@ public TestCategory Category { get { - var testMethodAnnotation = Declaration.Annotations.OfType().First(); + var testMethodAnnotation = Declaration.Annotations.Where(pta => pta.Annotation is TestMethodAnnotation).First(); + var argument = testMethodAnnotation.AnnotationArguments.FirstOrDefault()?.UnQuote(); - var categorization = testMethodAnnotation.Category.Equals(string.Empty) ? TestExplorer.TestExplorer_Uncategorized : testMethodAnnotation.Category; + var categorization = string.IsNullOrWhiteSpace(argument) + ? TestExplorer.TestExplorer_Uncategorized + : argument; return new TestCategory(categorization); } } diff --git a/RubberduckTests/Annotations/AnnotationResolutionTests.cs b/RubberduckTests/Annotations/AnnotationResolutionTests.cs index 9c567025a7..7644a99f26 100644 --- a/RubberduckTests/Annotations/AnnotationResolutionTests.cs +++ b/RubberduckTests/Annotations/AnnotationResolutionTests.cs @@ -571,10 +571,10 @@ public void AnnotationArgumentIsRecognisedWithWhiteSpaceInBetween() using (var state = MockParser.CreateAndParse(vbe.Object)) { var declaration = state.DeclarationFinder.UserDeclarations(DeclarationType.Function).Single(); - var annotation = declaration.Annotations.OfType().Single(); + var annotation = declaration.Annotations.Where(pta => pta.Annotation is DescriptionAnnotation).Single(); - var expectedAnnotationArgument = "Function description"; - var actualAnnotationArgument = annotation.Description; + var expectedAnnotationArgument = "\"Function description\""; + var actualAnnotationArgument = annotation.AnnotationArguments[0]; Assert.AreEqual(expectedAnnotationArgument, actualAnnotationArgument); } @@ -594,10 +594,10 @@ public void AnnotationArgumentIsRecognisedWithLineContinuationsInBetween() using (var state = MockParser.CreateAndParse(vbe.Object)) { var declaration = state.DeclarationFinder.UserDeclarations(DeclarationType.Function).Single(); - var annotation = declaration.Annotations.OfType().Single(); + var annotation = declaration.Annotations.Where(pta => pta.Annotation is DescriptionAnnotation).Single(); - var expectedAnnotationArgument = "Function description"; - var actualAnnotationArgument = annotation.Description; + var expectedAnnotationArgument = "\"Function description\""; + var actualAnnotationArgument = annotation.AnnotationArguments[0]; Assert.AreEqual(expectedAnnotationArgument, actualAnnotationArgument); } diff --git a/RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs b/RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs index d0fc84e9a1..0249bc6cc4 100644 --- a/RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs +++ b/RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs @@ -15,10 +15,10 @@ public class AttributeAnnotationProviderTests public void FindMemberAnnotationForRandomAttributeReturnsMemberAttributeAnnotation() { var attributeName = "VB_Whatever"; - var attributeValues = new List{"SomeValue"}; + var attributeValues = new List{ "\"SomeValue\"" }; var expectedAnnotationType = "MemberAttribute"; - var expectedValues = new List{"VB_Whatever", "SomeValue"}; + var expectedValues = new List{ "VB_Whatever", "\"SomeValue\"" }; var attributeAnnotationProvider = GetAnnotationProvider(); var (actualAnnotationInfo, actualValues) = attributeAnnotationProvider.MemberAttributeAnnotation(attributeName, attributeValues); @@ -31,10 +31,10 @@ public void FindMemberAnnotationForRandomAttributeReturnsMemberAttributeAnnotati public void FindModuleAnnotationForRandomAttributeReturnsModuleAttributeAnnotation() { var attributeName = "VB_Whatever"; - var attributeValues = new List { "SomeValue" }; + var attributeValues = new List { "\"SomeValue\"" }; var expectedAnnotationType = "ModuleAttribute"; - var expectedValues = new List { "VB_Whatever", "SomeValue" }; + var expectedValues = new List { "VB_Whatever", "\"SomeValue\"" }; var attributeAnnotationProvider = GetAnnotationProvider(); var (annotationInfo, actualValues) = attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues); @@ -81,7 +81,7 @@ public void MemberAttributeAnnotationReturnsSpecializedAnnotationsWhereApplicabl private AttributeAnnotationProvider GetAnnotationProvider() { - return new AttributeAnnotationProvider(MockParser.GetWellKnownAnnotationTypes().Where(annot => typeof(IAttributeAnnotation).IsAssignableFrom(annot))); + return new AttributeAnnotationProvider(MockParser.GetWellKnownAnnotations().OfType()); } private static void AssertEqual(IReadOnlyList expectedList, IReadOnlyList actualList) diff --git a/RubberduckTests/CodeExplorer/CodeExplorerComponentViewModelTests.cs b/RubberduckTests/CodeExplorer/CodeExplorerComponentViewModelTests.cs index f0e967c34a..bc957ad54c 100644 --- a/RubberduckTests/CodeExplorer/CodeExplorerComponentViewModelTests.cs +++ b/RubberduckTests/CodeExplorer/CodeExplorerComponentViewModelTests.cs @@ -457,7 +457,7 @@ private static Declaration PredeclaredClassDeclaration(Declaration project) project, PredeclaredClassName, true, - Enumerable.Empty(), + Enumerable.Empty(), attributes); } } diff --git a/RubberduckTests/CodeExplorer/CodeExplorerFolderTests.cs b/RubberduckTests/CodeExplorer/CodeExplorerFolderTests.cs index c48fb04942..77d38003bc 100644 --- a/RubberduckTests/CodeExplorer/CodeExplorerFolderTests.cs +++ b/RubberduckTests/CodeExplorer/CodeExplorerFolderTests.cs @@ -1,6 +1,7 @@ using NUnit.Framework; using Rubberduck.Navigation.CodeExplorer; using Rubberduck.Parsing.Annotations; +using Rubberduck.Parsing.Grammar; using Rubberduck.Parsing.Symbols; using Rubberduck.VBEditor; using Rubberduck.VBEditor.SafeComWrappers; @@ -105,10 +106,10 @@ Sub Foo() var folder = (CodeExplorerCustomFolderViewModel)explorer.ViewModel.SelectedItem; var declarations = project.State.AllUserDeclarations.ToList(); - var annotation = new FolderAnnotation(new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(1, 1)), null, new[] { "\"First\"" }); - var predeclared = new PredeclaredIdAnnotation(new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(2, 1)), null, Enumerable.Empty()); + var annotation = new ParseTreeAnnotation(new FolderAnnotation(), new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(1, 1)), new[] { "\"First\"" }); + var predeclared = new ParseTreeAnnotation(new PredeclaredIdAnnotation(), new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(2, 1)), (VBAParser.AnnotationContext)null); - declarations.Add(GetNewClassDeclaration(project.Declaration, "Foo", new IAnnotation [] { annotation, predeclared })); + declarations.Add(GetNewClassDeclaration(project.Declaration, "Foo", new ParseTreeAnnotation[] { annotation, predeclared })); project.Synchronize(ref declarations); var added = folder.Children.OfType().Single(); @@ -137,16 +138,16 @@ Sub Foo() var folder = (CodeExplorerCustomFolderViewModel)explorer.ViewModel.SelectedItem; var declarations = project.State.AllUserDeclarations.ToList(); - var annotation = new FolderAnnotation(new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(2, 1)), null, new[] { "\"First\"" }); - var predeclared = new PredeclaredIdAnnotation(new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(1, 1)), null, Enumerable.Empty()); + var annotation = new ParseTreeAnnotation(new FolderAnnotation(), new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(2, 1)), new[] { "First" }); + var predeclared = new ParseTreeAnnotation(new PredeclaredIdAnnotation(), new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(1, 1)), (VBAParser.AnnotationContext)null); - declarations.Add(GetNewClassDeclaration(project.Declaration, "Foo", new IAnnotation[] { predeclared, annotation })); + declarations.Add(GetNewClassDeclaration(project.Declaration, "Foo", new ParseTreeAnnotation[] { predeclared, annotation })); project.Synchronize(ref declarations); var added = folder.Children.OfType().Single(); Assert.AreEqual(DeclarationType.ClassModule, added.Declaration.DeclarationType); - Assert.AreEqual("\"First\"", added.Declaration.CustomFolder); + Assert.AreEqual("First", added.Declaration.CustomFolder); } } @@ -356,13 +357,13 @@ public void FoldersNamesAreCaseSensitive() private static Declaration GetNewClassDeclaration(Declaration project, string name, string folder = "") { var annotations = string.IsNullOrEmpty(folder) - ? Enumerable.Empty() - : new[] { new FolderAnnotation(new QualifiedSelection(project.QualifiedModuleName, new Selection(1, 1)), null, new[] { folder }) }; + ? Enumerable.Empty() + : new[] { new ParseTreeAnnotation(new FolderAnnotation(), new QualifiedSelection(project.QualifiedModuleName, new Selection(1, 1)), new[] { folder }) }; return GetNewClassDeclaration(project, name, annotations); } - private static Declaration GetNewClassDeclaration(Declaration project, string name, IEnumerable annotations) + private static Declaration GetNewClassDeclaration(Declaration project, string name, IEnumerable annotations) { var declaration = new ClassModuleDeclaration(new QualifiedMemberName(project.QualifiedModuleName, name), project, name, true, annotations, new Attributes()); diff --git a/RubberduckTests/Commands/UnitTestCommandTests.cs b/RubberduckTests/Commands/UnitTestCommandTests.cs index 6500d25958..567c69d048 100644 --- a/RubberduckTests/Commands/UnitTestCommandTests.cs +++ b/RubberduckTests/Commands/UnitTestCommandTests.cs @@ -56,7 +56,7 @@ public void AddsTest(Type command) addTestMethodCommand.Execute(null); var added = state.DeclarationFinder.AllUserDeclarations.SingleOrDefault(test => - test.Annotations.Any(annotation => annotation is TestMethodAnnotation)); + test.Annotations.Any(pta => pta.Annotation is TestMethodAnnotation)); Assert.NotNull(added); } @@ -321,7 +321,7 @@ End Property var testModule = state.DeclarationFinder.FindStdModule($"{TestModuleBaseName}1", project); - Assert.IsTrue(testModule.Annotations.Any(a => a is TestModuleAnnotation)); + Assert.IsTrue(testModule.Annotations.Any(a => a.Annotation is TestModuleAnnotation)); var stubIdentifierNames = new List { @@ -375,7 +375,7 @@ End Property var testModule = state.DeclarationFinder.FindStdModule($"{TestModuleBaseName}1", project); - Assert.IsTrue(testModule.Annotations.Any(a => a is TestModuleAnnotation)); + Assert.IsTrue(testModule.Annotations.Any(a => a.Annotation is TestModuleAnnotation)); var stubs = state.DeclarationFinder.AllUserDeclarations.Where(d => d.IdentifierName.EndsWith(TestMethodBaseName)).ToList(); Assert.AreEqual(0, stubs.Count); @@ -419,7 +419,7 @@ End Enum var testModule = state.DeclarationFinder.FindStdModule($"{TestModuleBaseName}1", project); - Assert.IsTrue(testModule.Annotations.Any(a => a is TestModuleAnnotation)); + Assert.IsTrue(testModule.Annotations.Any(a => a.Annotation is TestModuleAnnotation)); var stubs = state.DeclarationFinder.AllUserDeclarations.Where(d => d.IdentifierName.EndsWith(TestMethodBaseName)).ToList(); Assert.AreEqual(0, stubs.Count); diff --git a/RubberduckTests/Grammar/AnnotationTests.cs b/RubberduckTests/Grammar/AnnotationTests.cs index 5810cf9835..7a60266b73 100644 --- a/RubberduckTests/Grammar/AnnotationTests.cs +++ b/RubberduckTests/Grammar/AnnotationTests.cs @@ -11,42 +11,42 @@ namespace RubberduckTests.Grammar [Category("Annotations")] public class AnnotationTests { - [TestCase(typeof(DefaultMemberAnnotation), "DefaultMember", new[] { "param" })] - [TestCase(typeof(DescriptionAnnotation), "Description", new[] { "desc" })] - [TestCase(typeof(EnumeratorMemberAnnotation), "Enumerator", new[] { "param" })] - [TestCase(typeof(ExcelHotKeyAnnotation), "ExcelHotkey", new [] { "A" })] + [TestCase(typeof(DefaultMemberAnnotation), "DefaultMember")] + [TestCase(typeof(DescriptionAnnotation), "Description")] + [TestCase(typeof(EnumeratorMemberAnnotation), "Enumerator")] + [TestCase(typeof(ExcelHotKeyAnnotation), "ExcelHotkey")] [TestCase(typeof(ExposedModuleAnnotation), "Exposed")] - [TestCase(typeof(FolderAnnotation), "Folder", new[] { "param" })] + [TestCase(typeof(FolderAnnotation), "Folder")] [TestCase(typeof(IgnoreAnnotation), "Ignore")] [TestCase(typeof(IgnoreModuleAnnotation), "IgnoreModule")] [TestCase(typeof(IgnoreTestAnnotation), "IgnoreTest")] [TestCase(typeof(InterfaceAnnotation), "Interface")] - [TestCase(typeof(MemberAttributeAnnotation), "MemberAttribute", new[] { "Attribute", "Value" })] - [TestCase(typeof(ModuleAttributeAnnotation), "ModuleAttribute", new[] { "Attribute", "Value" })] + [TestCase(typeof(MemberAttributeAnnotation), "MemberAttribute")] + [TestCase(typeof(ModuleAttributeAnnotation), "ModuleAttribute")] [TestCase(typeof(ModuleCleanupAnnotation), "ModuleCleanup")] - [TestCase(typeof(ModuleDescriptionAnnotation), "ModuleDescription", new[] { "desc" })] + [TestCase(typeof(ModuleDescriptionAnnotation), "ModuleDescription")] [TestCase(typeof(ModuleInitializeAnnotation), "ModuleInitialize")] [TestCase(typeof(NoIndentAnnotation), "NoIndent")] [TestCase(typeof(NotRecognizedAnnotation), "NotRecognized")] - [TestCase(typeof(ObsoleteAnnotation), "Obsolete", new [] { "justification" })] + [TestCase(typeof(ObsoleteAnnotation), "Obsolete")] [TestCase(typeof(PredeclaredIdAnnotation), "PredeclaredId")] [TestCase(typeof(TestCleanupAnnotation), "TestCleanup")] [TestCase(typeof(TestInitializeAnnotation), "TestInitialize")] [TestCase(typeof(TestMethodAnnotation), "TestMethod")] [TestCase(typeof(TestModuleAnnotation), "TestModule")] - [TestCase(typeof(VariableDescriptionAnnotation), "VariableDescription", new[] { "desc" })] - public void AnnotationTypes_MatchExpectedAnnotationNames(Type annotationType, string name, IEnumerable args = null) + [TestCase(typeof(VariableDescriptionAnnotation), "VariableDescription")] + public void AnnotationTypes_MatchExpectedAnnotationNames(Type annotationType, string expectedName) { - var annotation = (IAnnotation) Activator.CreateInstance(annotationType, new QualifiedSelection(), null, args ?? new List()); - Assert.AreEqual(name, annotation.AnnotationType); + IAnnotation annotation = (IAnnotation)Activator.CreateInstance(annotationType); + Assert.AreEqual(expectedName, annotation.Name); } [TestCase(typeof(IgnoreAnnotation))] [TestCase(typeof(IgnoreModuleAnnotation))] public void AnnotationTypes_MultipleApplicationsAllowed(Type annotationType) { - var annotation = (IAnnotation)Activator.CreateInstance(annotationType, new QualifiedSelection(), null, null); - Assert.IsTrue(annotation.MetaInformation.AllowMultiple); + IAnnotation annotation = (IAnnotation)Activator.CreateInstance(annotationType); + Assert.IsTrue(annotation.AllowMultiple); } } } \ No newline at end of file diff --git a/RubberduckTests/Grammar/ResolverTests.cs b/RubberduckTests/Grammar/ResolverTests.cs index 85e4c8e3b7..5fd0d57952 100644 --- a/RubberduckTests/Grammar/ResolverTests.cs +++ b/RubberduckTests/Grammar/ResolverTests.cs @@ -1384,16 +1384,16 @@ End Sub "; using (var state = Resolve(code)) { - var declaration = state.AllUserDeclarations.Single(item => item.DeclarationType == DeclarationType.Variable && !item.IsUndeclared); var usage = declaration.References.Single(); - var annotation = (IgnoreAnnotation) usage.Annotations.First(); + var annotation = usage.Annotations.First(); + Assert.IsInstanceOf(annotation.Annotation); Assert.IsTrue( usage.Annotations.Count() == 1 - && annotation.InspectionNames.Count() == 1 - && annotation.InspectionNames.First() == "UnassignedVariableUsage"); + && annotation.AnnotationArguments.Count() == 1 + && annotation.AnnotationArguments.First() == "UnassignedVariableUsage"); } } @@ -1418,13 +1418,14 @@ End Sub var usage = declaration.References.Single(); - var annotation1 = (IgnoreAnnotation)usage.Annotations.ElementAt(0); - var annotation2 = (IgnoreAnnotation)usage.Annotations.ElementAt(1); + var annotation1 = usage.Annotations.ElementAt(0); + var annotation2 = usage.Annotations.ElementAt(1); Assert.AreEqual(2, usage.Annotations.Count()); - - Assert.IsTrue(usage.Annotations.Any(a => ((IgnoreAnnotation)a).InspectionNames.First() == "UseMeaningfulName")); - Assert.IsTrue(usage.Annotations.Any(a => ((IgnoreAnnotation)a).InspectionNames.First() == "UnassignedVariableUsage")); + Assert.IsInstanceOf(annotation1.Annotation); + Assert.IsInstanceOf(annotation2.Annotation); + Assert.IsTrue(usage.Annotations.Any(a => a.AnnotationArguments.First() == "UseMeaningfulName")); + Assert.IsTrue(usage.Annotations.Any(a => a.AnnotationArguments.First() == "UnassignedVariableUsage")); } } @@ -1445,8 +1446,8 @@ public void AnnotatedDeclaration_LinesAbove_HaveAnnotations() var declaration = state.AllUserDeclarations.First(f => f.DeclarationType == DeclarationType.Procedure); Assert.AreEqual(2, declaration.Annotations.Count(), "Annotation count mismatch"); - Assert.IsTrue(declaration.Annotations.Any(a => a is TestMethodAnnotation)); - Assert.IsTrue(declaration.Annotations.Any(a => a is IgnoreTestAnnotation)); + Assert.IsTrue(declaration.Annotations.Any(a => a.Annotation is TestMethodAnnotation)); + Assert.IsTrue(declaration.Annotations.Any(a => a.Annotation is IgnoreTestAnnotation)); } } @@ -2879,9 +2880,9 @@ End Sub var declaration = state.AllUserDeclarations.Single(item => item.IdentifierName == "orgs"); - var annotation = declaration.Annotations.SingleOrDefault(item => item is IgnoreAnnotation); + var annotation = declaration.Annotations.SingleOrDefault(item => item.Annotation is IgnoreAnnotation); Assert.IsNotNull(annotation); - Assert.IsTrue(results.SequenceEqual(((IgnoreAnnotation)annotation).InspectionNames)); + Assert.IsTrue(results.SequenceEqual(annotation.AnnotationArguments)); } } @@ -2905,9 +2906,9 @@ End Sub var declaration = state.AllUserDeclarations.Single(item => item.IdentifierName == "orgs"); - var annotation = declaration.Annotations.SingleOrDefault(item => item is IgnoreAnnotation); + var annotation = declaration.Annotations.SingleOrDefault(item => item.Annotation is IgnoreAnnotation); Assert.IsNotNull(annotation); - Assert.IsTrue(results.SequenceEqual(((IgnoreAnnotation)annotation).InspectionNames)); + Assert.IsTrue(results.SequenceEqual(annotation.AnnotationArguments)); } } diff --git a/RubberduckTests/Inspections/AttributeValueOutOfSyncInspectionTests.cs b/RubberduckTests/Inspections/AttributeValueOutOfSyncInspectionTests.cs index 4f1b924b47..0254dfb1d2 100644 --- a/RubberduckTests/Inspections/AttributeValueOutOfSyncInspectionTests.cs +++ b/RubberduckTests/Inspections/AttributeValueOutOfSyncInspectionTests.cs @@ -218,9 +218,10 @@ public void ResultContainsAnnotationAndAttributeValues() var inspectionResults = InspectionResults(inputCode); var inspectionResult = inspectionResults.First(); - Assert.IsInstanceOf(inspectionResult.Properties.Annotation); - Assert.AreEqual("VB_UserMemId", inspectionResult.Properties.Annotation.Attribute); - Assert.AreEqual("-4", inspectionResult.Properties.Annotation.AttributeValues[0]); + + Assert.IsInstanceOf(inspectionResult.Properties.Annotation.Annotation); + Assert.AreEqual("VB_UserMemId", inspectionResult.Properties.AttributeName); + Assert.AreEqual("-4", ((ParseTreeAnnotation)inspectionResult.Properties.Annotation).AttributeValues()[0]); Assert.AreEqual("40", inspectionResult.Properties.AttributeValues[0]); } diff --git a/RubberduckTests/Inspections/InspectionResultTests.cs b/RubberduckTests/Inspections/InspectionResultTests.cs index 44053b3501..54eb562fa4 100644 --- a/RubberduckTests/Inspections/InspectionResultTests.cs +++ b/RubberduckTests/Inspections/InspectionResultTests.cs @@ -140,7 +140,7 @@ public void IdentifierRefereneceInspectionResultsAreDeemedInvalidatedIfTheModule var modifiedModules = new HashSet { declarationModule }; var declarationFinderProviderMock = new Mock(); - var declaratioFinder = new DeclarationFinder(new List(), new List(), + var declaratioFinder = new DeclarationFinder(new List(), new List(), new List(), new Dictionary>()); declarationFinderProviderMock.SetupGet(m => m.DeclarationFinder).Returns(declaratioFinder); var inspectionResult = new IdentifierReferenceInspectionResult(inspectionMock.Object, string.Empty, declarationFinderProviderMock.Object, identifierReference); @@ -169,7 +169,7 @@ public void IdentifierReferenceInspectionResultsAreNotDeemedInvalidatedIfNeither var modifiedModules = new HashSet { otherModule }; var declarationFinderProviderMock = new Mock(); - var declaratioFinder = new DeclarationFinder(new List(), new List(), + var declaratioFinder = new DeclarationFinder(new List(), new List(), new List(), new Dictionary>()); declarationFinderProviderMock.SetupGet(m => m.DeclarationFinder).Returns(declaratioFinder); var inspectionResult = new IdentifierReferenceInspectionResult(inspectionMock.Object, string.Empty, declarationFinderProviderMock.Object, identifierReference); diff --git a/RubberduckTests/Inspections/UntypedFunctionUsageInspectionTests.cs b/RubberduckTests/Inspections/UntypedFunctionUsageInspectionTests.cs index a47c478122..43862cbde3 100644 --- a/RubberduckTests/Inspections/UntypedFunctionUsageInspectionTests.cs +++ b/RubberduckTests/Inspections/UntypedFunctionUsageInspectionTests.cs @@ -143,7 +143,7 @@ private List GetBuiltInDeclarations() vbaDeclaration, "Conversion", false, - new List(), + new List(), new Attributes()); var fileSystemModule = new ProceduralModuleDeclaration( @@ -151,7 +151,7 @@ private List GetBuiltInDeclarations() vbaDeclaration, "FileSystem", false, - new List(), + new List(), new Attributes()); var interactionModule = new ProceduralModuleDeclaration( @@ -159,7 +159,7 @@ private List GetBuiltInDeclarations() vbaDeclaration, "Interaction", false, - new List(), + new List(), new Attributes()); var stringsModule = new ProceduralModuleDeclaration( @@ -167,7 +167,7 @@ private List GetBuiltInDeclarations() vbaDeclaration, "Strings", false, - new List(), + new List(), new Attributes()); var dateTimeModule = new ProceduralModuleDeclaration( @@ -175,7 +175,7 @@ private List GetBuiltInDeclarations() vbaDeclaration, "Strings", false, - new List(), + new List(), new Attributes()); var hiddenModule = new ProceduralModuleDeclaration( @@ -183,7 +183,7 @@ private List GetBuiltInDeclarations() vbaDeclaration, "_HiddenModule", false, - new List(), + new List(), new Attributes()); @@ -200,7 +200,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var environFunction = new FunctionDeclaration( @@ -216,7 +216,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var rtrimFunction = new FunctionDeclaration( @@ -232,7 +232,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var chrFunction = new FunctionDeclaration( @@ -248,7 +248,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var formatFunction = new FunctionDeclaration( @@ -264,7 +264,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstFormatParam = new ParameterDeclaration( @@ -311,7 +311,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstRightParam = new ParameterDeclaration( @@ -338,7 +338,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var leftbFunction = new FunctionDeclaration( @@ -354,7 +354,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstLeftBParam = new ParameterDeclaration( @@ -381,7 +381,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var leftFunction = new FunctionDeclaration( @@ -397,7 +397,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstLeftParam = new ParameterDeclaration( @@ -424,7 +424,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstRightBParam = new ParameterDeclaration( @@ -451,7 +451,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstMidBParam = new ParameterDeclaration( @@ -488,7 +488,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var trimFunction = new FunctionDeclaration( @@ -504,7 +504,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var ltrimFunction = new FunctionDeclaration( @@ -520,7 +520,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var midFunction = new FunctionDeclaration( @@ -536,7 +536,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstMidParam = new ParameterDeclaration( @@ -573,7 +573,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var octFunction = new FunctionDeclaration( @@ -589,7 +589,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var errorFunction = new FunctionDeclaration( @@ -605,7 +605,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var strFunction = new FunctionDeclaration( @@ -621,7 +621,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var curDirFunction = new FunctionDeclaration( @@ -637,7 +637,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var datePropertyGet = new PropertyGetDeclaration( @@ -653,7 +653,7 @@ private List GetBuiltInDeclarations() new Selection(), false, false, - new List(), + new List(), new Attributes()); @@ -670,7 +670,7 @@ private List GetBuiltInDeclarations() new Selection(), false, false, - new List(), + new List(), new Attributes()); var inputbFunction = new FunctionDeclaration( @@ -686,7 +686,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstInputBParam = new ParameterDeclaration( @@ -723,7 +723,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstInputParam = new ParameterDeclaration( diff --git a/RubberduckTests/Mocks/MockParser.cs b/RubberduckTests/Mocks/MockParser.cs index 0a4cba4738..aac9ea2363 100644 --- a/RubberduckTests/Mocks/MockParser.cs +++ b/RubberduckTests/Mocks/MockParser.cs @@ -76,7 +76,7 @@ public static (SynchronousParseCoordinator parser, IRewritingManager rewritingMa var mainTokenStreamParser = new VBATokenStreamParser(mainParseErrorListenerFactory, mainParseErrorListenerFactory); var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider(); var stringParser = new TokenStreamParserStringParserAdapterWithPreprocessing(tokenStreamProvider, mainTokenStreamParser, preprocessor); - var vbaParserAnnotationFactory = new VBAParserAnnotationFactory(GetWellKnownAnnotationTypes()); + var vbaParserAnnotationFactory = new VBAParserAnnotationFactory(GetWellKnownAnnotations()); var projectManager = new RepositoryProjectManager(projectRepository); var moduleToModuleReferenceManager = new ModuleToModuleReferenceManager(); var supertypeClearer = new SynchronousSupertypeClearer(state); @@ -162,12 +162,13 @@ public static (SynchronousParseCoordinator parser, IRewritingManager rewritingMa return (parser, rewritingManager); } - public static IEnumerable GetWellKnownAnnotationTypes() + public static IEnumerable GetWellKnownAnnotations() { return Assembly.GetAssembly(typeof(IAnnotation)) .GetTypes() .Where(candidate => typeof(IAnnotation).IsAssignableFrom(candidate) - && !candidate.IsAbstract); + && !candidate.IsAbstract) + .Select(t => (IAnnotation)Activator.CreateInstance(t)); } public static SynchronousParseCoordinator Create(IVBE vbe, RubberduckParserState state, IProjectsRepository projectRepository, string serializedComProjectsPath = null) diff --git a/RubberduckTests/PostProcessing/AnnotationUpdaterTests.cs b/RubberduckTests/PostProcessing/AnnotationUpdaterTests.cs index 22d8983065..972055996d 100644 --- a/RubberduckTests/PostProcessing/AnnotationUpdaterTests.cs +++ b/RubberduckTests/PostProcessing/AnnotationUpdaterTests.cs @@ -42,7 +42,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = new AnnotationAttribute("MemberAttribute", AnnotationTarget.Member); + var annotationToAdd = new MemberAttributeAnnotation(); var annotationValues = new List { "VB_Ext_Key", "\"Key\"", "\"Value\"" }; string actualCode; @@ -96,7 +96,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = new AnnotationAttribute("ModuleAttribute", AnnotationTarget.Module); + var annotationToAdd = new ModuleAttributeAnnotation(); var annotationValues = new List { "VB_Ext_Key", "\"Key\"", "\"Value\"" }; string actualCode; @@ -143,7 +143,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = new AnnotationAttribute("ModuleAttribute", AnnotationTarget.Module); + var annotationToAdd = new ModuleAttributeAnnotation(); var annotationValues = new List { "VB_Ext_Key", "\"Key\"", "\"Value\"" }; string actualCode; @@ -196,7 +196,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = new AnnotationAttribute("MemberAttribute", AnnotationTarget.Member); + var annotationToAdd = new MemberAttributeAnnotation(); var annotationValues = new List { "VB_Ext_Key", "\"Key\"", "\"Value\"" }; string actualCode; @@ -254,7 +254,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = new AnnotationAttribute("Ignore", AnnotationTarget.General); + var annotationToAdd = new IgnoreAnnotation(); var annotationValues = new List { "ObsoleteMemberUsage" }; string actualCode; @@ -301,7 +301,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = new AnnotationAttribute("Obsolete", AnnotationTarget.Member | AnnotationTarget.Variable); + var annotationToAdd = new ObsoleteAnnotation(); string actualCode; var (component, rewriteSession, state) = TestSetup(inputCode); @@ -347,7 +347,7 @@ End Sub bar = vbNullString End Sub "; - var annotationToAdd = new AnnotationAttribute("Obsolete", AnnotationTarget.Member | AnnotationTarget.Variable); + var annotationToAdd = new ObsoleteAnnotation(); string actualCode; var (component, rewriteSession, state) = TestSetup(inputCode); @@ -674,7 +674,7 @@ Option Explicit var moduleDeclaration = state.DeclarationFinder .UserDeclarations(DeclarationType.ProceduralModule) .First(); - var annotationsToRemove = moduleDeclaration.Annotations.Where(annotation => !(annotation is ExposedModuleAnnotation)); + var annotationsToRemove = moduleDeclaration.Annotations.Where(pta => !(pta.Annotation is ExposedModuleAnnotation)); var annotationUpdater = new AnnotationUpdater(); annotationUpdater.RemoveAnnotations(rewriteSession, annotationsToRemove); @@ -718,7 +718,7 @@ End Sub bar = vbNullString End Sub "; - var newAnnotation = new AnnotationAttribute("MemberAttribute", AnnotationTarget.Member); + var newAnnotation = new MemberAttributeAnnotation(); var newAnnotationValues = new List { "VB_ExtKey", "\"Key\"", "\"Value\"" }; string actualCode; @@ -728,7 +728,7 @@ End Sub var fooDeclaration = state.DeclarationFinder .UserDeclarations(DeclarationType.Procedure) .First(decl => decl.IdentifierName == "Foo"); - var annotationToUpdate = fooDeclaration.Annotations.First(annotation => annotation is DescriptionAnnotation); + var annotationToUpdate = fooDeclaration.Annotations.First(pta => pta.Annotation is DescriptionAnnotation); var annotationUpdater = new AnnotationUpdater(); annotationUpdater.UpdateAnnotation(rewriteSession, annotationToUpdate, newAnnotation, newAnnotationValues); diff --git a/RubberduckTests/QuickFixes/AddAttributeAnnotationQuickFixTests.cs b/RubberduckTests/QuickFixes/AddAttributeAnnotationQuickFixTests.cs index 73f24b6e3b..7c6b05e608 100644 --- a/RubberduckTests/QuickFixes/AddAttributeAnnotationQuickFixTests.cs +++ b/RubberduckTests/QuickFixes/AddAttributeAnnotationQuickFixTests.cs @@ -18,7 +18,7 @@ public class AddAttributeAnnotationQuickFixTests : QuickFixTestBase public void KnownModuleAttributeWithoutAnnotation_QuickFixWorks() { const string inputCode = - @"Attribute VB_PredeclaredID = True + @"Attribute VB_PredeclaredId = True Public Sub Foo() Const const1 As Integer = 9 End Sub"; @@ -26,7 +26,7 @@ public void KnownModuleAttributeWithoutAnnotation_QuickFixWorks() //So adding on top is OK. const string expectedCode = @"'@PredeclaredId -Attribute VB_PredeclaredID = True +Attribute VB_PredeclaredId = True Public Sub Foo() Const const1 As Integer = 9 End Sub"; @@ -62,7 +62,7 @@ public void UnknownModuleAttributeWithoutAnnotation_QuickFixWorks() public void KnownModuleAttributeWithoutAnnotationWhileOtherAttributeWithAnnotationPresent_QuickFixWorks() { const string inputCode = - @"Attribute VB_PredeclaredID = True + @"Attribute VB_PredeclaredId = True Attribute VB_Exposed = True '@Exposed Public Sub Foo() @@ -72,7 +72,7 @@ public void KnownModuleAttributeWithoutAnnotationWhileOtherAttributeWithAnnotati //So adding on top is OK. const string expectedCode = @"'@PredeclaredId -Attribute VB_PredeclaredID = True +Attribute VB_PredeclaredId = True Attribute VB_Exposed = True '@Exposed Public Sub Foo() @@ -158,7 +158,7 @@ protected override IQuickFix QuickFix(RubberduckParserState state) { // FIXME actually inject the annotations here... return new AddAttributeAnnotationQuickFix(new AnnotationUpdater(), - new AttributeAnnotationProvider(MockParser.GetWellKnownAnnotationTypes().Where(annotation => typeof(IAttributeAnnotation).IsAssignableFrom(annotation)))); + new AttributeAnnotationProvider(MockParser.GetWellKnownAnnotations().OfType())); } } } \ No newline at end of file diff --git a/RubberduckTests/QuickFixes/AdjustAttributeAnnotationQuickFixTests.cs b/RubberduckTests/QuickFixes/AdjustAttributeAnnotationQuickFixTests.cs index b75b4cfa0f..c57833bad9 100644 --- a/RubberduckTests/QuickFixes/AdjustAttributeAnnotationQuickFixTests.cs +++ b/RubberduckTests/QuickFixes/AdjustAttributeAnnotationQuickFixTests.cs @@ -110,7 +110,7 @@ protected override IVBE TestVbe(string code, out IVBComponent component) protected override IQuickFix QuickFix(RubberduckParserState state) { return new AdjustAttributeAnnotationQuickFix(new AnnotationUpdater(), - new AttributeAnnotationProvider(MockParser.GetWellKnownAnnotationTypes().Where(annotation => typeof(IAttributeAnnotation).IsAssignableFrom(annotation)))); + new AttributeAnnotationProvider(MockParser.GetWellKnownAnnotations().OfType())); } } } \ No newline at end of file diff --git a/RubberduckTests/QuickFixes/RemoveDuplicatedAnnotationQuickFixTests.cs b/RubberduckTests/QuickFixes/RemoveDuplicatedAnnotationQuickFixTests.cs index 36ec8cdb29..195446c4c2 100644 --- a/RubberduckTests/QuickFixes/RemoveDuplicatedAnnotationQuickFixTests.cs +++ b/RubberduckTests/QuickFixes/RemoveDuplicatedAnnotationQuickFixTests.cs @@ -182,7 +182,7 @@ public void RemoveDuplicatedAnnotation_QuickFixWorks_RemoveDuplicatesOfOnlyOneAn '@TestMethod Public Sub Foo End Sub"; - Func conditionToFix = result => result.Properties.AnnotationType == typeof(ObsoleteAnnotation); + Func conditionToFix = result => result.Properties.AnnotationType is ObsoleteAnnotation; var actualCode = ApplyQuickFixToFirstInspectionResultSatisfyingPredicate(inputCode, state => new DuplicatedAnnotationInspection(state), conditionToFix); Assert.AreEqual(expectedCode, actualCode); } diff --git a/RubberduckTests/Refactoring/Rename/RenameTests.cs b/RubberduckTests/Refactoring/Rename/RenameTests.cs index 6d9a478a3c..458fa59267 100644 --- a/RubberduckTests/Refactoring/Rename/RenameTests.cs +++ b/RubberduckTests/Refactoring/Rename/RenameTests.cs @@ -803,8 +803,8 @@ End Sub public void RenamePresenter_WarnsAboutControlEventHandlerRename_AbortsOnDeniedConfirmation() { var qmn = new QualifiedModuleName("TestProject", string.Empty, "TestComponent"); - var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); - var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); var model = new RenameModel(originalTargetDeclaration) { @@ -822,8 +822,8 @@ public void RenamePresenter_WarnsAboutControlEventHandlerRename_AbortsOnDeniedCo public void RenamePresenter_WarnsAboutControlEventHandlerRename_ContinuesAfterConfirmation() { var qmn = new QualifiedModuleName("TestProject", string.Empty, "TestComponent"); - var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); - var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); var model = new RenameModel(originalTargetDeclaration) { @@ -1232,8 +1232,8 @@ End Sub public void RenamePresenter_WarnsAboutEventHandlerRename_AbortsOnDeniedConfirmation() { var qmn = new QualifiedModuleName("TestProject", string.Empty, "TestComponent"); - var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); - var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); var model = new RenameModel(originalTargetDeclaration) { @@ -1251,8 +1251,8 @@ public void RenamePresenter_WarnsAboutEventHandlerRename_AbortsOnDeniedConfirmat public void RenamePresenter_WarnsAboutEventHandlerRename_ContinuesAfterConfirmation() { var qmn = new QualifiedModuleName("TestProject", string.Empty, "TestComponent"); - var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); - var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); var model = new RenameModel(originalTargetDeclaration) { @@ -1501,8 +1501,8 @@ End Sub public void RenamePresenter_WarnsAboutInterfaceVariableImplementationRename_AbortsOnDeniedConfirmation() { var qmn = new QualifiedModuleName("TestProject", string.Empty, "TestComponent"); - var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn,"Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); - var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn,"Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); var model = new RenameModel(originalTargetDeclaration) { @@ -1520,8 +1520,8 @@ public void RenamePresenter_WarnsAboutInterfaceVariableImplementationRename_Abor public void RenamePresenter_WarnsAboutInterfaceVariableImplementationRename_ContinuesAfterConfirmation() { var qmn = new QualifiedModuleName("TestProject", string.Empty, "TestComponent"); - var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); - var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); var model = new RenameModel(originalTargetDeclaration) { diff --git a/RubberduckTests/Symbols/DeclarationFinderTests.cs b/RubberduckTests/Symbols/DeclarationFinderTests.cs index 44ee33212f..a92fa0562b 100644 --- a/RubberduckTests/Symbols/DeclarationFinderTests.cs +++ b/RubberduckTests/Symbols/DeclarationFinderTests.cs @@ -2122,7 +2122,7 @@ private static FunctionDeclaration GetTestFunction(Declaration moduleDeclatation private static void AddReference(Declaration toDeclaration, Declaration fromModuleDeclaration, ParserRuleContext context = null) { - toDeclaration.AddReference(toDeclaration.QualifiedName.QualifiedModuleName, fromModuleDeclaration, fromModuleDeclaration, context, toDeclaration.IdentifierName, toDeclaration, Selection.Home, new List()); + toDeclaration.AddReference(toDeclaration.QualifiedName.QualifiedModuleName, fromModuleDeclaration, fromModuleDeclaration, context, toDeclaration.IdentifierName, toDeclaration, Selection.Home, new List()); } } } \ No newline at end of file From 2868ed67351943d5c3537b7f631744d6a4eb6ea0 Mon Sep 17 00:00:00 2001 From: Vogel612 Date: Tue, 3 Sep 2019 23:55:33 +0200 Subject: [PATCH 3/4] Address PullRequest comments This means an interface IParseTreeAnnotation has been extracted. Additionally the CW registration has been adjusted, multiple minor fixes and tweaks to usage sites have been done. IAnnotation now exposes a method to allow dealing with annotation arguments as they are added to the ParseTreeAnnotation itself. By default that just passes the arguments through. --- .../AttributeValueOutOfSyncInspection.cs | 16 +++-- .../DuplicatedAnnotationInspection.cs | 2 +- .../Concrete/IllegalAnnotationInspection.cs | 4 +- .../Concrete/MissingAttributeInspection.cs | 12 ++-- .../MissingMemberAnnotationInspection.cs | 7 ++- .../MissingModuleAnnotationInspection.cs | 7 ++- .../Concrete/ObsoleteMemberUsageInspection.cs | 3 +- .../QuickFixes/AddMissingAttributeQuickFix.cs | 10 ++- .../AdjustAttributeAnnotationQuickFix.cs | 2 +- .../AdjustAttributeValuesQuickFix.cs | 7 ++- .../RemoveDuplicatedAnnotationQuickFix.cs | 2 +- .../Root/RubberduckIoCInstaller.cs | 21 ++----- .../Annotations/AnnotationBase.cs | 6 ++ .../Annotations/AnnotationListener.cs | 6 +- .../AttributeAnnotationExtensions.cs | 17 ++--- .../DefaultMemberAnnotation.cs | 0 .../DescriptionAnnotation.cs | 0 .../DescriptionAttributeAnnotationBase.cs | 0 .../EnumeratorMemberAnnotation.cs | 0 .../ExcelHotKeyAnnotation.cs | 1 + .../ExposedModuleAnnotation.cs | 0 .../FixedAttributeValueAnnotationBase.cs | 0 .../FlexibleAttributeAnnotationBase.cs | 0 .../FlexibleAttributeValueAnnotationBase.cs | 11 ++-- .../FolderAnnotation.cs | 0 .../IgnoreAnnotation.cs | 0 .../IgnoreModuleAnnotation.cs | 0 .../IgnoreTestAnnotation.cs | 0 .../InterfaceAnnotation.cs | 0 .../MemberAttributeAnnotation.cs | 0 .../ModuleAttributeAnnotation.cs | 0 .../ModuleCleanupAnnotation.cs | 0 .../ModuleDescriptionAnnotation.cs | 0 .../ModuleInitializeAnnotation.cs | 0 .../NoIndentAnnotation.cs | 0 .../NotRecognizedAnnotation.cs | 0 .../ObsoleteAnnotation.cs | 0 .../PredeclaredIdAnnotation.cs | 0 .../TestCleanupAnnotation.cs | 0 .../TestInitializeAnnotation.cs | 0 .../Concrete/TestMethodAnnotation.cs | 30 +++++++++ .../TestModuleAnnotation.cs | 0 .../VariableDescriptionAnnotation.cs | 0 Rubberduck.Parsing/Annotations/IAnnotation.cs | 3 + .../Annotations/IAnnotationFactory.cs | 2 +- .../Annotations/IParseTreeAnnotation.cs | 18 ++++++ .../Implementations/TestMethodAnnotation.cs | 29 --------- .../Annotations/ParseTreeAnnotation.cs | 22 +------ .../Annotations/VBAParserAnnotationFactory.cs | 6 +- Rubberduck.Parsing/Symbols/Attributes.cs | 10 +-- .../Symbols/ClassModuleDeclaration.cs | 6 +- Rubberduck.Parsing/Symbols/Declaration.cs | 12 ++-- .../DeclarationLoaders/AliasDeclarations.cs | 58 ++++++++--------- .../DeclarationLoaders/DebugDeclarations.cs | 10 +-- .../FormEventDeclarations.cs | 12 ++-- .../SpecialFormDeclarations.cs | 4 +- .../Symbols/DocumentModuleDeclaration.cs | 2 +- .../Symbols/EventDeclaration.cs | 2 +- .../Symbols/ExternalProcedureDeclaration.cs | 2 +- .../Symbols/FunctionDeclaration.cs | 2 +- .../Symbols/IDeclarationFinderFactory.cs | 2 +- .../Symbols/IdentifierReference.cs | 6 +- .../Symbols/ModuleBodyElementDeclaration.cs | 2 +- .../Symbols/ModuleDeclaration.cs | 4 +- .../Symbols/ProceduralModuleDeclaration.cs | 8 +-- .../Symbols/PropertyDeclaration.cs | 2 +- .../Symbols/PropertyGetDeclaration.cs | 2 +- .../Symbols/PropertyLetDeclaration.cs | 2 +- .../Symbols/PropertySetDeclaration.cs | 2 +- .../Symbols/SubroutineDeclaration.cs | 2 +- .../Symbols/UnboundMemberDeclaration.cs | 2 +- .../Symbols/ValuedDeclaration.cs | 2 +- .../Symbols/VariableDeclaration.cs | 2 +- Rubberduck.Parsing/VBA/AnnotationUpdater.cs | 6 +- ...oncurrentlyConstructedDeclarationFinder.cs | 2 +- ...ntlyConstructedDeclarationFinderFactory.cs | 2 +- .../DeclarationCaching/DeclarationFinder.cs | 16 ++--- .../DeclarationFinderFactory.cs | 2 +- .../DeclarationResolveRunnerBase.cs | 4 +- .../DeclarationSymbolsListener.cs | 14 ++--- Rubberduck.Parsing/VBA/IAnnotationUpdater.cs | 6 +- Rubberduck.Parsing/VBA/ModuleState.cs | 10 +-- .../VBA/Parsing/IModuleParser.cs | 4 +- .../VBA/Parsing/ModuleParser.cs | 2 +- .../BoundExpressionVisitor.cs | 2 +- .../IdentifierReferenceResolver.cs | 5 +- .../VBA/RubberduckParserState.cs | 12 ++-- .../UnitTesting/TestEngine.cs | 2 +- .../UnitTesting/TestMethod.cs | 2 +- .../AttributeAnnotationProviderTests.cs | 2 +- .../CodeExplorerComponentViewModelTests.cs | 2 +- .../CodeExplorer/CodeExplorerFolderTests.cs | 34 +++++++--- RubberduckTests/Grammar/AnnotationTests.cs | 20 ++++++ .../AttributeValueOutOfSyncInspectionTests.cs | 8 ++- .../Inspections/InspectionResultTests.cs | 4 +- .../UntypedFunctionUsageInspectionTests.cs | 62 +++++++++---------- RubberduckTests/Mocks/MockParser.cs | 4 +- .../AddAttributeAnnotationQuickFixTests.cs | 3 +- .../AdjustAttributeAnnotationQuickFixTests.cs | 2 +- ...RemoveDuplicatedAnnotationQuickFixTests.cs | 2 +- .../Refactoring/Rename/RenameTests.cs | 24 +++---- .../Symbols/DeclarationFinderTests.cs | 2 +- 102 files changed, 357 insertions(+), 305 deletions(-) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/DefaultMemberAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/DescriptionAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/DescriptionAttributeAnnotationBase.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/EnumeratorMemberAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/ExcelHotKeyAnnotation.cs (99%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/ExposedModuleAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/FixedAttributeValueAnnotationBase.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/FlexibleAttributeAnnotationBase.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/FlexibleAttributeValueAnnotationBase.cs (80%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/FolderAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/IgnoreAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/IgnoreModuleAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/IgnoreTestAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/InterfaceAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/MemberAttributeAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/ModuleAttributeAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/ModuleCleanupAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/ModuleDescriptionAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/ModuleInitializeAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/NoIndentAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/NotRecognizedAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/ObsoleteAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/PredeclaredIdAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/TestCleanupAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/TestInitializeAnnotation.cs (100%) create mode 100644 Rubberduck.Parsing/Annotations/Concrete/TestMethodAnnotation.cs rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/TestModuleAnnotation.cs (100%) rename Rubberduck.Parsing/Annotations/{Implementations => Concrete}/VariableDescriptionAnnotation.cs (100%) create mode 100644 Rubberduck.Parsing/Annotations/IParseTreeAnnotation.cs delete mode 100644 Rubberduck.Parsing/Annotations/Implementations/TestMethodAnnotation.cs diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs index 7e46b8f99e..38886b8486 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs @@ -55,10 +55,11 @@ protected override IEnumerable DoGetInspectionResults() { foreach (var annotationInstance in declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation)) { - var annotation = annotationInstance.Annotation; + // cast is safe given the predicate in the foreach + var annotation = (IAttributeAnnotation)annotationInstance.Annotation; if (HasDifferingAttributeValues(declaration, annotationInstance, out var attributeValues)) { - var attributeName = annotationInstance.Attribute(); + var attributeName = annotation.Attribute(annotationInstance); var description = string.Format(InspectionResults.AttributeValueOutOfSyncInspection, attributeName, @@ -79,9 +80,14 @@ protected override IEnumerable DoGetInspectionResults() return results; } - private static bool HasDifferingAttributeValues(Declaration declaration, ParseTreeAnnotation annotationInstance, out IReadOnlyList attributeValues) + private static bool HasDifferingAttributeValues(Declaration declaration, IParseTreeAnnotation annotationInstance, out IReadOnlyList attributeValues) { - var attribute = annotationInstance.Attribute(); + if (!(annotationInstance.Annotation is IAttributeAnnotation annotation)) + { + attributeValues = new List(); + return false; + } + var attribute = annotation.Attribute(annotationInstance); var attributeNodes = declaration.DeclarationType.HasFlag(DeclarationType.Module) ? declaration.Attributes.AttributeNodesFor(annotationInstance) : declaration.Attributes.AttributeNodesFor(annotationInstance, declaration.IdentifierName); @@ -89,7 +95,7 @@ private static bool HasDifferingAttributeValues(Declaration declaration, ParseTr foreach (var attributeNode in attributeNodes) { var values = attributeNode.Values; - if (!annotationInstance.AttributeValues().SequenceEqual(values)) + if (!annotation.AttributeValues(annotationInstance).SequenceEqual(values)) { attributeValues = values; return true; diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs index fe4ffeb47d..f0da7bac6f 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs @@ -54,7 +54,7 @@ protected override IEnumerable DoGetInspectionResults() var result = new DeclarationInspectionResult( this, string.Format(InspectionResults.DuplicatedAnnotationInspection, duplicate.Key.ToString()), declaration); - result.Properties.AnnotationType = duplicate.Key; + result.Properties.Annotation = duplicate.Key; return result; })); } diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs index abb5502556..b2dc5f31c0 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs @@ -65,7 +65,7 @@ protected override IEnumerable DoGetInspectionResults() new QualifiedContext(annotation.QualifiedSelection.QualifiedName, annotation.Context))); } - private static IEnumerable UnboundAnnotations(IEnumerable annotations, IEnumerable userDeclarations, IEnumerable identifierReferences) + private static IEnumerable UnboundAnnotations(IEnumerable annotations, IEnumerable userDeclarations, IEnumerable identifierReferences) { var boundAnnotationsSelections = userDeclarations .SelectMany(declaration => declaration.Annotations) @@ -76,7 +76,7 @@ private static IEnumerable UnboundAnnotations(IEnumerable

!boundAnnotationsSelections.Contains(annotation.QualifiedSelection)).ToList(); } - private static IEnumerable AttributeAnnotationsInDocuments(IEnumerable userDeclarations) + private static IEnumerable AttributeAnnotationsInDocuments(IEnumerable userDeclarations) { var declarationsInDocuments = userDeclarations .Where(declaration => declaration.QualifiedModuleName.ComponentType == ComponentType.Document); diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs index 5915a1de08..5d9649d95d 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs @@ -72,16 +72,20 @@ protected override IEnumerable DoGetInspectionResults() return results; } - private static bool MissesCorrespondingAttribute(Declaration declaration, ParseTreeAnnotation annotation) + private static bool MissesCorrespondingAttribute(Declaration declaration, IParseTreeAnnotation annotationInstance) { - var attribute = annotation.Attribute(); + if (!(annotationInstance.Annotation is IAttributeAnnotation annotation)) + { + return false; + } + var attribute = annotation.Attribute(annotationInstance); if (string.IsNullOrEmpty(attribute)) { return false; } return declaration.DeclarationType.HasFlag(DeclarationType.Module) - ? !declaration.Attributes.HasAttributeFor(annotation) - : !declaration.Attributes.HasAttributeFor(annotation, declaration.IdentifierName); + ? !declaration.Attributes.HasAttributeFor(annotationInstance) + : !declaration.Attributes.HasAttributeFor(annotationInstance, declaration.IdentifierName); } } } \ No newline at end of file diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs index 35c1e98ca6..9f4aba2322 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs @@ -92,11 +92,14 @@ private static bool MissesCorrespondingMemberAnnotation(Declaration declaration, if (attributeBaseName == "VB_Ext_Key") { return !declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation) - .Any(annotation => annotation.Attribute().Equals("VB_Ext_Key") && attribute.Values[0].Equals(annotation.AttributeValues()[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) - .Any(annotation => annotation.Attribute().Equals(attributeBaseName)); + .Any(pta => ((IAttributeAnnotation)pta.Annotation).Attribute(pta).Equals(attributeBaseName)); } private static string AttributeBaseName(Declaration declaration, AttributeNode attribute) diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs index 05fab86ffa..602f58e1f0 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs @@ -97,11 +97,14 @@ private static bool MissesCorrespondingModuleAnnotation(Declaration declaration, if (attribute.Name == "VB_Ext_Key") { return !declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation) - .Any(annotation => annotation.Attribute().Equals("VB_Ext_Key") && attribute.Values[0].Equals(annotation.AttributeValues()[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) - .Any(annotation => annotation.Attribute().Equals(attribute.Name)); + .Any(pta => ((IAttributeAnnotation)pta.Annotation).Attribute(pta).Equals(attribute.Name)); } } } \ No newline at end of file diff --git a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs index 94024512f2..409048ff5e 100644 --- a/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs +++ b/Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs @@ -66,7 +66,8 @@ protected override IEnumerable DoGetInspectionResults() { var replacementDocumentation = declaration.Annotations .First(pta => pta.Annotation is ObsoleteAnnotation) - .AnnotationArguments.FirstOrDefault() ?? string.Empty; + .AnnotationArguments + .FirstOrDefault() ?? string.Empty; issues.AddRange(declaration.References.Select(reference => new IdentifierReferenceInspectionResult(this, diff --git a/Rubberduck.CodeAnalysis/QuickFixes/AddMissingAttributeQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/AddMissingAttributeQuickFix.cs index 1c075b6391..1f2b811d67 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/AddMissingAttributeQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/AddMissingAttributeQuickFix.cs @@ -22,13 +22,17 @@ public AddMissingAttributeQuickFix(IAttributesUpdater attributesUpdater) public override void Fix(IInspectionResult result, IRewriteSession rewriteSession) { var declaration = result.Target; - ParseTreeAnnotation annotationInstance = result.Properties.Annotation; - var attribute = annotationInstance.Attribute(); + IParseTreeAnnotation annotationInstance = result.Properties.Annotation; + if (!(annotationInstance.Annotation is IAttributeAnnotation annotation)) + { + return; + } + var attribute = annotation.Attribute(annotationInstance); var attributeName = declaration.DeclarationType.HasFlag(DeclarationType.Module) ? attribute : $"{declaration.IdentifierName}.{attribute}"; - _attributesUpdater.AddAttribute(rewriteSession, declaration, attributeName, annotationInstance.AttributeValues()); + _attributesUpdater.AddAttribute(rewriteSession, declaration, attributeName, annotation.AttributeValues(annotationInstance)); } public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.AddMissingAttributeQuickFix; diff --git a/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeAnnotationQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeAnnotationQuickFix.cs index fe28d30c3b..19ffc3a766 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeAnnotationQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeAnnotationQuickFix.cs @@ -25,7 +25,7 @@ public AdjustAttributeAnnotationQuickFix(IAnnotationUpdater annotationUpdater, I public override void Fix(IInspectionResult result, IRewriteSession rewriteSession) { - ParseTreeAnnotation oldAnnotation = result.Properties.Annotation; + IParseTreeAnnotation oldAnnotation = result.Properties.Annotation; string attributeName = result.Properties.AttributeName; IReadOnlyList attributeValues = result.Properties.AttributeValues; diff --git a/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeValuesQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeValuesQuickFix.cs index 54e2fe228a..04c835cc9d 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeValuesQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeValuesQuickFix.cs @@ -24,16 +24,17 @@ public AdjustAttributeValuesQuickFix(IAttributesUpdater attributesUpdater) public override void Fix(IInspectionResult result, IRewriteSession rewriteSession) { var declaration = result.Target; - ParseTreeAnnotation annotationInstance = result.Properties.Annotation; + IParseTreeAnnotation annotationInstance = result.Properties.Annotation; + // FIXME consider dealing with the implicit assumption here? IAttributeAnnotation annotation = (IAttributeAnnotation)annotationInstance.Annotation; IReadOnlyList attributeValues = result.Properties.AttributeValues; - var attribute = annotationInstance.Attribute(); + var attribute = annotation.Attribute(annotationInstance); var attributeName = declaration.DeclarationType.HasFlag(DeclarationType.Module) ? attribute : $"{declaration.IdentifierName}.{attribute}"; - _attributesUpdater.UpdateAttribute(rewriteSession, declaration, attributeName, annotationInstance.AttributeValues(), oldValues: attributeValues); + _attributesUpdater.UpdateAttribute(rewriteSession, declaration, attributeName, annotation.AttributeValues(annotationInstance), oldValues: attributeValues); } public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.AdjustAttributeValuesQuickFix; diff --git a/Rubberduck.CodeAnalysis/QuickFixes/RemoveDuplicatedAnnotationQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/RemoveDuplicatedAnnotationQuickFix.cs index 8832112462..14552c1e47 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/RemoveDuplicatedAnnotationQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/RemoveDuplicatedAnnotationQuickFix.cs @@ -20,7 +20,7 @@ public RemoveDuplicatedAnnotationQuickFix(IAnnotationUpdater annotationUpdater) public override void Fix(IInspectionResult result, IRewriteSession rewriteSession) { var duplicateAnnotations = result.Target.Annotations - .Where(pta => pta.Annotation == result.Properties.AnnotationType) + .Where(pta => pta.Annotation == result.Properties.Annotation) .OrderBy(annotation => annotation.AnnotatedLine) .Skip(1) .ToList(); diff --git a/Rubberduck.Main/Root/RubberduckIoCInstaller.cs b/Rubberduck.Main/Root/RubberduckIoCInstaller.cs index d625949907..e9f887189d 100644 --- a/Rubberduck.Main/Root/RubberduckIoCInstaller.cs +++ b/Rubberduck.Main/Root/RubberduckIoCInstaller.cs @@ -928,10 +928,7 @@ private void RegisterParsingEngine(IWindsorContainer container) container.Register(Component.For() .ImplementedBy() .DependsOn(Dependency.OnComponent("codePaneSourceCodeProvider", "CodeModuleSourceCodeHandler"), - Dependency.OnComponent("attributesSourceCodeProvider", "SourceFileSourceCodeHandler") - // TODO not sure whether this explicit registration is necessary - //,Dependency.OnComponent(typeof(IAnnotationFactory), typeof(VBAParserAnnotationFactory)) - ) + Dependency.OnComponent("attributesSourceCodeProvider", "SourceFileSourceCodeHandler")) .LifestyleSingleton()); container.Register(Component.For() .ImplementedBy() @@ -952,20 +949,14 @@ private void RegisterParsingEngine(IWindsorContainer container) private void RegisterAnnotationProcessing(IWindsorContainer container) { - var annotations = new List(); foreach (Assembly referenced in AssembliesToRegister()) { - annotations.AddRange(referenced.ExportedTypes - .Where(candidate => candidate.IsBasedOn(typeof(IAnnotation)) && !candidate.IsAbstract)); + container.Register(Classes.FromAssembly(referenced) + .IncludeNonPublicTypes() + .BasedOn() + .WithServiceAllInterfaces() + .LifestyleSingleton()); } - container.Register(Component.For() - .ImplementedBy() - .DependsOn(Dependency.OnValue>(annotations)) - .LifestyleSingleton()); - container.Register(Component.For() - .ImplementedBy() - .DependsOn(Dependency.OnValue>(annotations.Where(annotation => annotation.IsBasedOn(typeof(IAttributeAnnotation))))) - .LifestyleSingleton()); } private void RegisterTypeLibApi(IWindsorContainer container) diff --git a/Rubberduck.Parsing/Annotations/AnnotationBase.cs b/Rubberduck.Parsing/Annotations/AnnotationBase.cs index a0d4eb3635..e1eaaca38a 100644 --- a/Rubberduck.Parsing/Annotations/AnnotationBase.cs +++ b/Rubberduck.Parsing/Annotations/AnnotationBase.cs @@ -1,4 +1,5 @@ using System; +using System.Collections.Generic; using System.Linq; using Rubberduck.Parsing.Grammar; using Rubberduck.VBEditor; @@ -17,5 +18,10 @@ public AnnotationBase(string name, AnnotationTarget target, bool allowMultiple = Target = target; AllowMultiple = allowMultiple; } + + public virtual IReadOnlyList ProcessAnnotationArguments(IEnumerable arguments) + { + return arguments.ToList(); + } } } diff --git a/Rubberduck.Parsing/Annotations/AnnotationListener.cs b/Rubberduck.Parsing/Annotations/AnnotationListener.cs index 14ef9c606e..4d07456a66 100644 --- a/Rubberduck.Parsing/Annotations/AnnotationListener.cs +++ b/Rubberduck.Parsing/Annotations/AnnotationListener.cs @@ -7,18 +7,18 @@ namespace Rubberduck.Parsing.Annotations { public sealed class AnnotationListener : VBAParserBaseListener { - private readonly List _annotations; + private readonly List _annotations; private readonly IAnnotationFactory _factory; private readonly QualifiedModuleName _qualifiedName; public AnnotationListener(IAnnotationFactory factory, QualifiedModuleName qualifiedName) { - _annotations = new List(); + _annotations = new List(); _factory = factory; _qualifiedName = qualifiedName; } - public IEnumerable Annotations => _annotations; + public IEnumerable Annotations => _annotations; public override void ExitAnnotation([NotNull] VBAParser.AnnotationContext context) { diff --git a/Rubberduck.Parsing/Annotations/AttributeAnnotationExtensions.cs b/Rubberduck.Parsing/Annotations/AttributeAnnotationExtensions.cs index de7beddc69..e355eea270 100644 --- a/Rubberduck.Parsing/Annotations/AttributeAnnotationExtensions.cs +++ b/Rubberduck.Parsing/Annotations/AttributeAnnotationExtensions.cs @@ -8,23 +8,14 @@ namespace Rubberduck.Parsing.Annotations { public static class AttributeAnnotationExtensions { - public static string Attribute(this ParseTreeAnnotation annotationInstance) + public static string Attribute(this IAttributeAnnotation annotation, IParseTreeAnnotation annotationInstance) { - if (annotationInstance.Annotation is IAttributeAnnotation annotation) - { - return annotation.Attribute(annotationInstance.AnnotationArguments); - } - return null; + return annotation.Attribute(annotationInstance.AnnotationArguments); } - public static IReadOnlyList AttributeValues(this ParseTreeAnnotation annotationInstance) + public static IReadOnlyList AttributeValues(this IAttributeAnnotation annotation, IParseTreeAnnotation instance) { - if (annotationInstance.Annotation is IAttributeAnnotation annotation) - { - return annotation.AnnotationToAttributeValues(annotationInstance.AnnotationArguments); - } - return null; - + return annotation.AnnotationToAttributeValues(instance.AnnotationArguments); } } } diff --git a/Rubberduck.Parsing/Annotations/Implementations/DefaultMemberAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/DefaultMemberAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/DefaultMemberAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/DefaultMemberAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/DescriptionAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/DescriptionAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/DescriptionAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/DescriptionAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/DescriptionAttributeAnnotationBase.cs b/Rubberduck.Parsing/Annotations/Concrete/DescriptionAttributeAnnotationBase.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/DescriptionAttributeAnnotationBase.cs rename to Rubberduck.Parsing/Annotations/Concrete/DescriptionAttributeAnnotationBase.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/EnumeratorMemberAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/EnumeratorMemberAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/EnumeratorMemberAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/EnumeratorMemberAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/ExcelHotKeyAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/ExcelHotKeyAnnotation.cs similarity index 99% rename from Rubberduck.Parsing/Annotations/Implementations/ExcelHotKeyAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/ExcelHotKeyAnnotation.cs index 662aa4c2e7..da3f411e85 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/ExcelHotKeyAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/Concrete/ExcelHotKeyAnnotation.cs @@ -12,6 +12,7 @@ public sealed class ExcelHotKeyAnnotation : FlexibleAttributeValueAnnotationBase public ExcelHotKeyAnnotation() : base("ExcelHotkey", AnnotationTarget.Member, "VB_ProcData.VB_Invoke_Func", 1) { } + public override IReadOnlyList AnnotationToAttributeValues(IReadOnlyList annotationValues) { return annotationValues.Take(1).Select(v => v.UnQuote()[0] + @"\n14".EnQuote()).ToList(); diff --git a/Rubberduck.Parsing/Annotations/Implementations/ExposedModuleAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/ExposedModuleAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/ExposedModuleAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/ExposedModuleAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/FixedAttributeValueAnnotationBase.cs b/Rubberduck.Parsing/Annotations/Concrete/FixedAttributeValueAnnotationBase.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/FixedAttributeValueAnnotationBase.cs rename to Rubberduck.Parsing/Annotations/Concrete/FixedAttributeValueAnnotationBase.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeAnnotationBase.cs b/Rubberduck.Parsing/Annotations/Concrete/FlexibleAttributeAnnotationBase.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeAnnotationBase.cs rename to Rubberduck.Parsing/Annotations/Concrete/FlexibleAttributeAnnotationBase.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeValueAnnotationBase.cs b/Rubberduck.Parsing/Annotations/Concrete/FlexibleAttributeValueAnnotationBase.cs similarity index 80% rename from Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeValueAnnotationBase.cs rename to Rubberduck.Parsing/Annotations/Concrete/FlexibleAttributeValueAnnotationBase.cs index 4750032bf7..f01b17a69b 100644 --- a/Rubberduck.Parsing/Annotations/Implementations/FlexibleAttributeValueAnnotationBase.cs +++ b/Rubberduck.Parsing/Annotations/Concrete/FlexibleAttributeValueAnnotationBase.cs @@ -9,20 +9,19 @@ namespace Rubberduck.Parsing.Annotations { public abstract class FlexibleAttributeValueAnnotationBase : AnnotationBase, IAttributeAnnotation { - public string Attribute { get; } - + private readonly string _attribute; private readonly int _numberOfValues; protected FlexibleAttributeValueAnnotationBase(string name, AnnotationTarget target, string attribute, int numberOfValues) : base(name, target) { - Attribute = attribute; + _attribute = attribute; _numberOfValues = numberOfValues; } public bool MatchesAttributeDefinition(string attributeName, IReadOnlyList attributeValues) { - return Attribute == attributeName && _numberOfValues == attributeValues.Count; + return _attribute == attributeName && _numberOfValues == attributeValues.Count; } public virtual IReadOnlyList AnnotationToAttributeValues(IReadOnlyList annotationValues) @@ -35,9 +34,9 @@ public virtual IReadOnlyList AttributeToAnnotationValues(IReadOnlyList v.EnQuote()).ToList(); } - string IAttributeAnnotation.Attribute(IReadOnlyList annotationValues) + public string Attribute(IReadOnlyList annotationValues) { - return Attribute; + return _attribute; } } } \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/FolderAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/FolderAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/FolderAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/FolderAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/IgnoreAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/IgnoreAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/IgnoreAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/IgnoreAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/IgnoreModuleAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/IgnoreModuleAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/IgnoreModuleAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/IgnoreModuleAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/IgnoreTestAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/IgnoreTestAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/IgnoreTestAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/IgnoreTestAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/InterfaceAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/InterfaceAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/InterfaceAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/InterfaceAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/MemberAttributeAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/MemberAttributeAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/MemberAttributeAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/MemberAttributeAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/ModuleAttributeAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/ModuleAttributeAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/ModuleAttributeAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/ModuleAttributeAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/ModuleCleanupAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/ModuleCleanupAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/ModuleCleanupAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/ModuleCleanupAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/ModuleDescriptionAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/ModuleDescriptionAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/ModuleDescriptionAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/ModuleDescriptionAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/ModuleInitializeAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/ModuleInitializeAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/ModuleInitializeAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/ModuleInitializeAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/NoIndentAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/NoIndentAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/NoIndentAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/NoIndentAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/NotRecognizedAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/NotRecognizedAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/NotRecognizedAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/NotRecognizedAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/ObsoleteAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/ObsoleteAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/ObsoleteAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/ObsoleteAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/PredeclaredIdAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/PredeclaredIdAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/PredeclaredIdAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/PredeclaredIdAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/TestCleanupAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/TestCleanupAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/TestCleanupAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/TestCleanupAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/TestInitializeAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/TestInitializeAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/TestInitializeAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/TestInitializeAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Concrete/TestMethodAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/TestMethodAnnotation.cs new file mode 100644 index 0000000000..89f83dc328 --- /dev/null +++ b/Rubberduck.Parsing/Annotations/Concrete/TestMethodAnnotation.cs @@ -0,0 +1,30 @@ +using System; +using Rubberduck.VBEditor; +using System.Collections.Generic; +using System.Linq; +using Rubberduck.Parsing.Grammar; +using Rubberduck.Common; + +namespace Rubberduck.Parsing.Annotations +{ + ///

+ /// Marks a method that the test engine will execute as a unit test. + /// + public sealed class TestMethodAnnotation : AnnotationBase + { + public TestMethodAnnotation() + : base("TestMethod", AnnotationTarget.Member) + { } + + public IReadOnlyList ProcessAnnotationArguments(IEnumerable arguments) + { + var firstParameter = arguments.FirstOrDefault()?.UnQuote(); + var result = new List(); + if (!string.IsNullOrWhiteSpace(firstParameter)) + { + result.Add(firstParameter); + } + return result; + } + } +} diff --git a/Rubberduck.Parsing/Annotations/Implementations/TestModuleAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/TestModuleAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/TestModuleAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/TestModuleAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/Implementations/VariableDescriptionAnnotation.cs b/Rubberduck.Parsing/Annotations/Concrete/VariableDescriptionAnnotation.cs similarity index 100% rename from Rubberduck.Parsing/Annotations/Implementations/VariableDescriptionAnnotation.cs rename to Rubberduck.Parsing/Annotations/Concrete/VariableDescriptionAnnotation.cs diff --git a/Rubberduck.Parsing/Annotations/IAnnotation.cs b/Rubberduck.Parsing/Annotations/IAnnotation.cs index 21718f4849..0245ad7c75 100644 --- a/Rubberduck.Parsing/Annotations/IAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/IAnnotation.cs @@ -1,6 +1,7 @@ using Rubberduck.Parsing.Grammar; using Rubberduck.VBEditor; using System; +using System.Collections.Generic; namespace Rubberduck.Parsing.Annotations { @@ -9,6 +10,8 @@ public interface IAnnotation string Name { get; } AnnotationTarget Target { get; } bool AllowMultiple { get; } + + IReadOnlyList ProcessAnnotationArguments(IEnumerable arguments); } [Flags] diff --git a/Rubberduck.Parsing/Annotations/IAnnotationFactory.cs b/Rubberduck.Parsing/Annotations/IAnnotationFactory.cs index d0a50d1b67..9aeef06338 100644 --- a/Rubberduck.Parsing/Annotations/IAnnotationFactory.cs +++ b/Rubberduck.Parsing/Annotations/IAnnotationFactory.cs @@ -5,6 +5,6 @@ namespace Rubberduck.Parsing.Annotations { public interface IAnnotationFactory { - ParseTreeAnnotation Create(VBAParser.AnnotationContext context, QualifiedSelection qualifiedSelection); + IParseTreeAnnotation Create(VBAParser.AnnotationContext context, QualifiedSelection qualifiedSelection); } } diff --git a/Rubberduck.Parsing/Annotations/IParseTreeAnnotation.cs b/Rubberduck.Parsing/Annotations/IParseTreeAnnotation.cs new file mode 100644 index 0000000000..e4d5a0d2cb --- /dev/null +++ b/Rubberduck.Parsing/Annotations/IParseTreeAnnotation.cs @@ -0,0 +1,18 @@ +using System.Collections.Generic; +using Rubberduck.Parsing.Grammar; +using Rubberduck.VBEditor; + +namespace Rubberduck.Parsing.Annotations +{ + public interface IParseTreeAnnotation + { + // needs to be accessible to all external consumers + IAnnotation Annotation { get; } + IReadOnlyList AnnotationArguments { get; } + + // needs to be accessible to IllegalAnnotationInspection + int? AnnotatedLine { get; } + VBAParser.AnnotationContext Context { get; } + QualifiedSelection QualifiedSelection { get; } + } +} \ No newline at end of file diff --git a/Rubberduck.Parsing/Annotations/Implementations/TestMethodAnnotation.cs b/Rubberduck.Parsing/Annotations/Implementations/TestMethodAnnotation.cs deleted file mode 100644 index 42c6538124..0000000000 --- a/Rubberduck.Parsing/Annotations/Implementations/TestMethodAnnotation.cs +++ /dev/null @@ -1,29 +0,0 @@ -using System; -using Rubberduck.VBEditor; -using System.Collections.Generic; -using System.Linq; -using Rubberduck.Parsing.Grammar; - -namespace Rubberduck.Parsing.Annotations -{ - /// - /// Marks a method that the test engine will execute as a unit test. - /// - public sealed class TestMethodAnnotation : AnnotationBase - { - public TestMethodAnnotation() - : base("TestMethod", AnnotationTarget.Member) - { - // FIXME unify handling of quoted arguments to annotations. - //// That should probably be part of VBAParserAnnotationFactory's handling of the annotationArguments context - //var firstParameter = parameters.FirstOrDefault(); - //if ((firstParameter?.StartsWith("\"") ?? false) && firstParameter.EndsWith("\"")) - //{ - // // Strip surrounding double quotes - // firstParameter = firstParameter.Substring(1, firstParameter.Length - 2); - //} - - //Category = string.IsNullOrWhiteSpace(firstParameter) ? string.Empty : firstParameter; - } - } -} diff --git a/Rubberduck.Parsing/Annotations/ParseTreeAnnotation.cs b/Rubberduck.Parsing/Annotations/ParseTreeAnnotation.cs index 5e3afe9d12..2455152416 100644 --- a/Rubberduck.Parsing/Annotations/ParseTreeAnnotation.cs +++ b/Rubberduck.Parsing/Annotations/ParseTreeAnnotation.cs @@ -8,7 +8,7 @@ namespace Rubberduck.Parsing.Annotations { - public class ParseTreeAnnotation + public class ParseTreeAnnotation : IParseTreeAnnotation { public const string ANNOTATION_MARKER = "@"; @@ -23,36 +23,20 @@ internal ParseTreeAnnotation(IAnnotation annotation, QualifiedSelection qualifie AnnotationArguments = AnnotationParametersFromContext(Context); } - // FIXME annotation constructor for unit-testing purposes alone! - internal ParseTreeAnnotation(IAnnotation annotation, QualifiedSelection qualifiedSelection, IEnumerable arguments) - { - Annotation = annotation; - QualifiedSelection = qualifiedSelection; - _annotatedLine = new Lazy(() => null); - Context = null; - AnnotationArguments = arguments.ToList(); - } - - // needs to be accessible to IllegalAnnotationInspection public QualifiedSelection QualifiedSelection { get; } public VBAParser.AnnotationContext Context { get; } public int? AnnotatedLine => _annotatedLine.Value; - // needs to be accessible to all external consumers public IAnnotation Annotation { get; } public IReadOnlyList AnnotationArguments { get; } - private static List AnnotationParametersFromContext(VBAParser.AnnotationContext context) + private List AnnotationParametersFromContext(VBAParser.AnnotationContext context) { var parameters = new List(); var argList = context?.annotationArgList(); if (argList != null) { - // CAUTION! THIS MUST NOT ADJUST THE QUOTING BEHAVIOUR! - // the reason for that is the different quoting requirements for attributes. - // some attributes require quoted values, some require unquoted values. - // we currently don't have a mechanism to specify which needs which - parameters.AddRange(argList.annotationArg().Select(arg => arg.GetText())); + parameters.AddRange(Annotation.ProcessAnnotationArguments(argList.annotationArg().Select(arg => arg.GetText()))); } return parameters; } diff --git a/Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs b/Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs index 34295eb40f..524567b85b 100644 --- a/Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs +++ b/Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs @@ -19,14 +19,14 @@ public VBAParserAnnotationFactory(IEnumerable recognizedAnnotations { unrecognized = annotation; } - _lookup.Add(annotation.Name.ToUpperInvariant(), annotation); + _lookup.Add(annotation.Name.ToLowerInvariant(), annotation); } } - public ParseTreeAnnotation Create(VBAParser.AnnotationContext context, QualifiedSelection qualifiedSelection) + public IParseTreeAnnotation Create(VBAParser.AnnotationContext context, QualifiedSelection qualifiedSelection) { var annotationName = context.annotationName().GetText(); - if (_lookup.TryGetValue(annotationName.ToUpperInvariant(), out var annotation)) + if (_lookup.TryGetValue(annotationName.ToLowerInvariant(), out var annotation)) { return new ParseTreeAnnotation(annotation, qualifiedSelection, context); } diff --git a/Rubberduck.Parsing/Symbols/Attributes.cs b/Rubberduck.Parsing/Symbols/Attributes.cs index 46628a79ce..1db7ea52ae 100644 --- a/Rubberduck.Parsing/Symbols/Attributes.cs +++ b/Rubberduck.Parsing/Symbols/Attributes.cs @@ -123,18 +123,18 @@ public static string MemberAttributeName(string attributeBaseName, string member return $"{memberName}.{attributeBaseName}"; } - public bool HasAttributeFor(ParseTreeAnnotation annotation, string memberName = null) + public bool HasAttributeFor(IParseTreeAnnotation annotation, string memberName = null) { return AttributeNodesFor(annotation, memberName).Any(); } - public IEnumerable AttributeNodesFor(ParseTreeAnnotation annotation, string memberName = null) + public IEnumerable AttributeNodesFor(IParseTreeAnnotation annotationInstance, string memberName = null) { - var attribute = annotation.Attribute(); - if (string.IsNullOrEmpty(attribute)) + if (!(annotationInstance.Annotation is IAttributeAnnotation annotation)) { return Enumerable.Empty(); } + var attribute = annotation.Attribute(annotationInstance); var attributeName = memberName != null ? MemberAttributeName(attribute, memberName) @@ -143,7 +143,7 @@ public IEnumerable AttributeNodesFor(ParseTreeAnnotation annotati if (attribute.Equals("VB_Ext_Key", StringComparison.OrdinalIgnoreCase)) { return this.Where(a => a.Name.Equals(attributeName, StringComparison.OrdinalIgnoreCase) - && a.Values[0] == annotation.AttributeValues()[0]); + && a.Values[0] == annotation.AttributeValues(annotationInstance)[0]); } return this.Where(a => a.Name.Equals(attributeName, StringComparison.OrdinalIgnoreCase)); diff --git a/Rubberduck.Parsing/Symbols/ClassModuleDeclaration.cs b/Rubberduck.Parsing/Symbols/ClassModuleDeclaration.cs index 0dbf2bc86e..4ac757a5eb 100644 --- a/Rubberduck.Parsing/Symbols/ClassModuleDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/ClassModuleDeclaration.cs @@ -24,7 +24,7 @@ public class ClassModuleDeclaration : ModuleDeclaration Declaration projectDeclaration, string name, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes, bool isWithEvents = false, bool hasDefaultInstanceVariable = false, @@ -62,7 +62,7 @@ public class ClassModuleDeclaration : ModuleDeclaration parent, coClass.Name, false, - new List(), + new List(), attributes, coClass.EventInterfaces.Any(), coClass.IsAppObject, @@ -86,7 +86,7 @@ public class ClassModuleDeclaration : ModuleDeclaration parent, @interface.Name, false, - new List(), + new List(), attributes) { } diff --git a/Rubberduck.Parsing/Symbols/Declaration.cs b/Rubberduck.Parsing/Symbols/Declaration.cs index 71f60987b0..48e84a6dab 100644 --- a/Rubberduck.Parsing/Symbols/Declaration.cs +++ b/Rubberduck.Parsing/Symbols/Declaration.cs @@ -37,7 +37,7 @@ public class Declaration : IEquatable bool isArray, VBAParser.AsTypeClauseContext asTypeContext, bool isUserDefined = true, - IEnumerable annotations = null, + IEnumerable annotations = null, Attributes attributes = null, bool undeclared = false) : this( @@ -76,7 +76,7 @@ public class Declaration : IEquatable bool isArray, VBAParser.AsTypeClauseContext asTypeContext, bool isUserDefined = true, - IEnumerable annotations = null, + IEnumerable annotations = null, Attributes attributes = null) : this( qualifiedName, @@ -114,7 +114,7 @@ public class Declaration : IEquatable bool isArray, VBAParser.AsTypeClauseContext asTypeContext, bool isUserDefined = true, - IEnumerable annotations = null, + IEnumerable annotations = null, Attributes attributes = null) { QualifiedName = qualifiedName; @@ -275,8 +275,8 @@ public static Declaration GetProjectParent(Declaration declaration) private ConcurrentDictionary _references = new ConcurrentDictionary(); public IEnumerable References => _references.Keys; - protected IEnumerable _annotations; - public IEnumerable Annotations => _annotations ?? new List(); + protected IEnumerable _annotations; + public IEnumerable Annotations => _annotations ?? new List(); private readonly Attributes _attributes; public Attributes Attributes => _attributes; @@ -359,7 +359,7 @@ private bool IsObjectOrObjectArray string identifier, Declaration callee, Selection selection, - IEnumerable annotations, + IEnumerable annotations, bool isAssignmentTarget = false, bool hasExplicitLetStatement = false, bool isSetAssigned = false, diff --git a/Rubberduck.Parsing/Symbols/DeclarationLoaders/AliasDeclarations.cs b/Rubberduck.Parsing/Symbols/DeclarationLoaders/AliasDeclarations.cs index a1295e3fc0..7ea0cf9a55 100644 --- a/Rubberduck.Parsing/Symbols/DeclarationLoaders/AliasDeclarations.cs +++ b/Rubberduck.Parsing/Symbols/DeclarationLoaders/AliasDeclarations.cs @@ -148,7 +148,7 @@ private PropertyGetDeclaration DatePropertyGet() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -167,7 +167,7 @@ private PropertyGetDeclaration TimePropertyGet() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -220,7 +220,7 @@ private FunctionDeclaration ErrorFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -239,7 +239,7 @@ private FunctionDeclaration HexFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -258,7 +258,7 @@ private FunctionDeclaration OctFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -277,7 +277,7 @@ private FunctionDeclaration StrFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -296,7 +296,7 @@ private FunctionDeclaration StrConvFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -315,7 +315,7 @@ private FunctionDeclaration CurDirFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -334,7 +334,7 @@ private FunctionDeclaration CommandFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -353,7 +353,7 @@ private FunctionDeclaration EnvironFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -372,7 +372,7 @@ private FunctionDeclaration ChrFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -391,7 +391,7 @@ private FunctionDeclaration ChrBFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -410,7 +410,7 @@ private FunctionDeclaration ChrwFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -429,7 +429,7 @@ private FunctionDeclaration FormatFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -448,7 +448,7 @@ private FunctionDeclaration LCaseFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -467,7 +467,7 @@ private FunctionDeclaration LeftFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -486,7 +486,7 @@ private FunctionDeclaration LeftBFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -505,7 +505,7 @@ private FunctionDeclaration LTrimFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -524,7 +524,7 @@ private FunctionDeclaration MidFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -543,7 +543,7 @@ private FunctionDeclaration MidBFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -562,7 +562,7 @@ private FunctionDeclaration TrimFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -581,7 +581,7 @@ private FunctionDeclaration RightFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -600,7 +600,7 @@ private FunctionDeclaration RightBFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -619,7 +619,7 @@ private FunctionDeclaration RTrimFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -638,7 +638,7 @@ private FunctionDeclaration SpaceFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -657,7 +657,7 @@ private FunctionDeclaration StringFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -676,7 +676,7 @@ private FunctionDeclaration UCaseFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -695,7 +695,7 @@ private FunctionDeclaration InputFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } @@ -714,7 +714,7 @@ private FunctionDeclaration InputBFunction() new Selection(), false, false, - new List(), + new List(), new Attributes()); } diff --git a/Rubberduck.Parsing/Symbols/DeclarationLoaders/DebugDeclarations.cs b/Rubberduck.Parsing/Symbols/DeclarationLoaders/DebugDeclarations.cs index ed294a8e01..c081b5f410 100644 --- a/Rubberduck.Parsing/Symbols/DeclarationLoaders/DebugDeclarations.cs +++ b/Rubberduck.Parsing/Symbols/DeclarationLoaders/DebugDeclarations.cs @@ -81,7 +81,7 @@ private static ProceduralModuleDeclaration DebugModuleDeclaration(Declaration pa parentProject, "DebugModule", false, - new List(), + new List(), new Attributes()); } @@ -101,7 +101,7 @@ private static ClassModuleDeclaration DebugClassDeclaration(Declaration parentPr parentProject, "DebugClass", false, - new List(), + new List(), new Attributes(), true); } @@ -129,7 +129,7 @@ private static Declaration DebugObjectDeclaration(ProceduralModuleDeclaration de false, null, false, - new List(), + new List(), new Attributes()); } @@ -145,7 +145,7 @@ private static SubroutineDeclaration DebugAssertDeclaration(ClassModuleDeclarati null, Selection.Home, false, - new List(), + new List(), new Attributes()); } @@ -161,7 +161,7 @@ private static SubroutineDeclaration DebugPrintDeclaration(ClassModuleDeclaratio null, Selection.Home, false, - new List(), + new List(), new Attributes()); } } diff --git a/Rubberduck.Parsing/Symbols/DeclarationLoaders/FormEventDeclarations.cs b/Rubberduck.Parsing/Symbols/DeclarationLoaders/FormEventDeclarations.cs index 745b8d078d..e24603e9e7 100644 --- a/Rubberduck.Parsing/Symbols/DeclarationLoaders/FormEventDeclarations.cs +++ b/Rubberduck.Parsing/Symbols/DeclarationLoaders/FormEventDeclarations.cs @@ -94,7 +94,7 @@ private static Declaration UserFormActivateEvent(Declaration formsClassModule) false, null, false, - new List(), + new List(), new Attributes()); } @@ -113,7 +113,7 @@ private static Declaration UserFormDeactivateEvent(Declaration formsClassModule) false, null, false, - new List(), + new List(), new Attributes()); } @@ -132,7 +132,7 @@ private static Declaration UserFormInitializeEvent(Declaration formsClassModule) false, null, false, - new List(), + new List(), new Attributes()); } @@ -151,7 +151,7 @@ private static Declaration UserFormQueryCloseEvent(Declaration formsClassModule) false, null, false, - new List(), + new List(), new Attributes()); } @@ -194,7 +194,7 @@ private static Declaration UserFormResizeEvent(Declaration formsClassModule) false, null, false, - new List(), + new List(), new Attributes()); } @@ -213,7 +213,7 @@ private static Declaration UserFormTerminateEvent(Declaration formsClassModule) false, null, false, - new List(), + new List(), new Attributes()); } diff --git a/Rubberduck.Parsing/Symbols/DeclarationLoaders/SpecialFormDeclarations.cs b/Rubberduck.Parsing/Symbols/DeclarationLoaders/SpecialFormDeclarations.cs index e30f97d641..b040aa665b 100644 --- a/Rubberduck.Parsing/Symbols/DeclarationLoaders/SpecialFormDeclarations.cs +++ b/Rubberduck.Parsing/Symbols/DeclarationLoaders/SpecialFormDeclarations.cs @@ -94,7 +94,7 @@ private static FunctionDeclaration LBoundFunctionWithoutParameters(Declaration p Selection.Home, false, false, - new List(), + new List(), new Attributes()); } @@ -133,7 +133,7 @@ private static FunctionDeclaration UBoundFunctionWithoutParameters(Declaration p Selection.Home, false, false, - new List(), + new List(), new Attributes()); } } diff --git a/Rubberduck.Parsing/Symbols/DocumentModuleDeclaration.cs b/Rubberduck.Parsing/Symbols/DocumentModuleDeclaration.cs index 371ffc4df6..681ba19ce7 100644 --- a/Rubberduck.Parsing/Symbols/DocumentModuleDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/DocumentModuleDeclaration.cs @@ -15,7 +15,7 @@ public class DocumentModuleDeclaration : ClassModuleDeclaration QualifiedMemberName qualifiedName, Declaration projectDeclaration, string name, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base(qualifiedName, projectDeclaration, diff --git a/Rubberduck.Parsing/Symbols/EventDeclaration.cs b/Rubberduck.Parsing/Symbols/EventDeclaration.cs index a0548b6bda..6cf229790f 100644 --- a/Rubberduck.Parsing/Symbols/EventDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/EventDeclaration.cs @@ -25,7 +25,7 @@ public sealed class EventDeclaration : Declaration, IParameterizedDeclaration Selection selection, bool isArray, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/ExternalProcedureDeclaration.cs b/Rubberduck.Parsing/Symbols/ExternalProcedureDeclaration.cs index fc60e9f9ff..a2d06fc9f2 100644 --- a/Rubberduck.Parsing/Symbols/ExternalProcedureDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/ExternalProcedureDeclaration.cs @@ -22,7 +22,7 @@ public sealed class ExternalProcedureDeclaration : Declaration, IParameterizedDe ParserRuleContext context, Selection selection, bool isUserDefined, - IEnumerable annotations) + IEnumerable annotations) : base( name, parent, diff --git a/Rubberduck.Parsing/Symbols/FunctionDeclaration.cs b/Rubberduck.Parsing/Symbols/FunctionDeclaration.cs index f99a6878e4..b3a55d8571 100644 --- a/Rubberduck.Parsing/Symbols/FunctionDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/FunctionDeclaration.cs @@ -24,7 +24,7 @@ public sealed class FunctionDeclaration : ModuleBodyElementDeclaration Selection selection, bool isArray, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/IDeclarationFinderFactory.cs b/Rubberduck.Parsing/Symbols/IDeclarationFinderFactory.cs index 489e26a9f5..7f1cc30adc 100644 --- a/Rubberduck.Parsing/Symbols/IDeclarationFinderFactory.cs +++ b/Rubberduck.Parsing/Symbols/IDeclarationFinderFactory.cs @@ -10,7 +10,7 @@ public interface IDeclarationFinderFactory { DeclarationFinder Create( IReadOnlyList declarations, - IEnumerable annotations, + IEnumerable annotations, IReadOnlyList unresolvedMemberDeclarations, IReadOnlyDictionary> unboundDefaultMemberAccesses, IHostApplication hostApp); diff --git a/Rubberduck.Parsing/Symbols/IdentifierReference.cs b/Rubberduck.Parsing/Symbols/IdentifierReference.cs index 02d1e1f01b..5087e26048 100644 --- a/Rubberduck.Parsing/Symbols/IdentifierReference.cs +++ b/Rubberduck.Parsing/Symbols/IdentifierReference.cs @@ -22,7 +22,7 @@ public class IdentifierReference : IEquatable Declaration declaration, bool isAssignmentTarget = false, bool hasExplicitLetStatement = false, - IEnumerable annotations = null, + IEnumerable annotations = null, bool isSetAssigned = false, bool isIndexedDefaultMemberAccess = false, bool isNonIndexedDefaultMemberAccess = false, @@ -43,7 +43,7 @@ public class IdentifierReference : IEquatable IsNonIndexedDefaultMemberAccess = isNonIndexedDefaultMemberAccess; DefaultMemberRecursionDepth = defaultMemberRecursionDepth; IsArrayAccess = isArrayAccess; - Annotations = annotations ?? new List(); + Annotations = annotations ?? new List(); } public QualifiedModuleName QualifiedModuleName { get; } @@ -79,7 +79,7 @@ public class IdentifierReference : IEquatable public Declaration Declaration { get; } - public IEnumerable Annotations { get; } + public IEnumerable Annotations { get; } public bool HasExplicitLetStatement { get; } diff --git a/Rubberduck.Parsing/Symbols/ModuleBodyElementDeclaration.cs b/Rubberduck.Parsing/Symbols/ModuleBodyElementDeclaration.cs index 650734b24e..9229db8b7e 100644 --- a/Rubberduck.Parsing/Symbols/ModuleBodyElementDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/ModuleBodyElementDeclaration.cs @@ -24,7 +24,7 @@ public abstract class ModuleBodyElementDeclaration : Declaration, IParameterized Selection selection, bool isArray, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/ModuleDeclaration.cs b/Rubberduck.Parsing/Symbols/ModuleDeclaration.cs index bce18a86a6..1124346770 100644 --- a/Rubberduck.Parsing/Symbols/ModuleDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/ModuleDeclaration.cs @@ -13,7 +13,7 @@ public abstract class ModuleDeclaration : Declaration string name, DeclarationType declarationType, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes, bool isWithEvents = false) : base( @@ -46,7 +46,7 @@ internal void AddMember(Declaration member) _members.Add(member); } - internal void RemoveAnnotations(ICollection annotationsToRemove) + internal void RemoveAnnotations(ICollection annotationsToRemove) { _annotations = _annotations?.Where(annotation => !annotationsToRemove.Contains(annotation)).ToList(); } diff --git a/Rubberduck.Parsing/Symbols/ProceduralModuleDeclaration.cs b/Rubberduck.Parsing/Symbols/ProceduralModuleDeclaration.cs index 21547e331e..7e964bffab 100644 --- a/Rubberduck.Parsing/Symbols/ProceduralModuleDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/ProceduralModuleDeclaration.cs @@ -13,7 +13,7 @@ public sealed class ProceduralModuleDeclaration : ModuleDeclaration Declaration projectDeclaration, string name, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( qualifiedName, @@ -32,7 +32,7 @@ public sealed class ProceduralModuleDeclaration : ModuleDeclaration parent, statics.Name, false, - new List(), + new List(), attributes) { IsPrivateModule = statics.IsRestricted; @@ -45,7 +45,7 @@ public ProceduralModuleDeclaration(ComEnumeration pseudo, Declaration parent, Qu parent, $"_{pseudo.Name}", false, - new List(), + new List(), new Attributes()) { } public ProceduralModuleDeclaration(ComStruct pseudo, Declaration parent, QualifiedModuleName module) @@ -54,7 +54,7 @@ public ProceduralModuleDeclaration(ComStruct pseudo, Declaration parent, Qualifi parent, $"_{pseudo.Name}", false, - new List(), + new List(), new Attributes()) { } public bool IsPrivateModule { get; internal set; } diff --git a/Rubberduck.Parsing/Symbols/PropertyDeclaration.cs b/Rubberduck.Parsing/Symbols/PropertyDeclaration.cs index 060272510e..a8baf2195f 100644 --- a/Rubberduck.Parsing/Symbols/PropertyDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/PropertyDeclaration.cs @@ -24,7 +24,7 @@ public abstract class PropertyDeclaration : ModuleBodyElementDeclaration Selection selection, bool isArray, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/PropertyGetDeclaration.cs b/Rubberduck.Parsing/Symbols/PropertyGetDeclaration.cs index aab155674a..e0d427bc14 100644 --- a/Rubberduck.Parsing/Symbols/PropertyGetDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/PropertyGetDeclaration.cs @@ -23,7 +23,7 @@ public sealed class PropertyGetDeclaration : PropertyDeclaration Selection selection, bool isArray, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/PropertyLetDeclaration.cs b/Rubberduck.Parsing/Symbols/PropertyLetDeclaration.cs index a322b3cbc2..91b0db4166 100644 --- a/Rubberduck.Parsing/Symbols/PropertyLetDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/PropertyLetDeclaration.cs @@ -21,7 +21,7 @@ public sealed class PropertyLetDeclaration : PropertyDeclaration ParserRuleContext attributesPassContext, Selection selection, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/PropertySetDeclaration.cs b/Rubberduck.Parsing/Symbols/PropertySetDeclaration.cs index 0a7450b6b4..fad11088d5 100644 --- a/Rubberduck.Parsing/Symbols/PropertySetDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/PropertySetDeclaration.cs @@ -22,7 +22,7 @@ public sealed class PropertySetDeclaration : PropertyDeclaration ParserRuleContext attributesPassContext, Selection selection, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/SubroutineDeclaration.cs b/Rubberduck.Parsing/Symbols/SubroutineDeclaration.cs index 2d0823c9a0..c7382aa90f 100644 --- a/Rubberduck.Parsing/Symbols/SubroutineDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/SubroutineDeclaration.cs @@ -21,7 +21,7 @@ public sealed class SubroutineDeclaration : ModuleBodyElementDeclaration ParserRuleContext attributesPassContext, Selection selection, bool isUserDefined, - IEnumerable annotations, + IEnumerable annotations, Attributes attributes) : base( name, diff --git a/Rubberduck.Parsing/Symbols/UnboundMemberDeclaration.cs b/Rubberduck.Parsing/Symbols/UnboundMemberDeclaration.cs index 085b8a7f06..0f3955aa5b 100644 --- a/Rubberduck.Parsing/Symbols/UnboundMemberDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/UnboundMemberDeclaration.cs @@ -16,7 +16,7 @@ public class UnboundMemberDeclaration : Declaration ///
public ParserRuleContext CallingContext { get; private set; } - public UnboundMemberDeclaration(Declaration parentDeclaration, ParserRuleContext unboundIdentifier, ParserRuleContext callingContext, IEnumerable annotations) : + public UnboundMemberDeclaration(Declaration parentDeclaration, ParserRuleContext unboundIdentifier, ParserRuleContext callingContext, IEnumerable annotations) : base(new QualifiedMemberName(parentDeclaration.QualifiedName.QualifiedModuleName, unboundIdentifier.GetText()), parentDeclaration, parentDeclaration, diff --git a/Rubberduck.Parsing/Symbols/ValuedDeclaration.cs b/Rubberduck.Parsing/Symbols/ValuedDeclaration.cs index 368f57b2d5..ebee682a3b 100644 --- a/Rubberduck.Parsing/Symbols/ValuedDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/ValuedDeclaration.cs @@ -17,7 +17,7 @@ public class ValuedDeclaration : Declaration string asTypeName, VBAParser.AsTypeClauseContext asTypeContext, string typeHint, - IEnumerable annotations, + IEnumerable annotations, Accessibility accessibility, DeclarationType declarationType, string value, diff --git a/Rubberduck.Parsing/Symbols/VariableDeclaration.cs b/Rubberduck.Parsing/Symbols/VariableDeclaration.cs index d945a288c6..69e6ebd8f0 100644 --- a/Rubberduck.Parsing/Symbols/VariableDeclaration.cs +++ b/Rubberduck.Parsing/Symbols/VariableDeclaration.cs @@ -23,7 +23,7 @@ public sealed class VariableDeclaration : Declaration, IInterfaceExposable Selection selection, bool isArray, VBAParser.AsTypeClauseContext asTypeContext, - IEnumerable annotations = null, + IEnumerable annotations = null, Attributes attributes = null) : base( qualifiedName, diff --git a/Rubberduck.Parsing/VBA/AnnotationUpdater.cs b/Rubberduck.Parsing/VBA/AnnotationUpdater.cs index 11e1a2f112..c665f37b8a 100644 --- a/Rubberduck.Parsing/VBA/AnnotationUpdater.cs +++ b/Rubberduck.Parsing/VBA/AnnotationUpdater.cs @@ -214,7 +214,7 @@ private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration dec AddAnnotation(rewriteSession, new QualifiedContext(reference.QualifiedModuleName, reference.Context), annotationInfo, annotationValues); } - public void RemoveAnnotation(IRewriteSession rewriteSession, ParseTreeAnnotation annotation) + public void RemoveAnnotation(IRewriteSession rewriteSession, IParseTreeAnnotation annotation) { if (annotation == null) { @@ -287,7 +287,7 @@ private static void RemoveAnnotationMarker(IModuleRewriter rewriter, VBAParser.A rewriter.RemoveRange(startOfAnnotationMarker, endOfAnnotationMarker); } - public void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable annotations) + public void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable annotations) { if (annotations == null) { @@ -330,7 +330,7 @@ public void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable newValues = null) + public void UpdateAnnotation(IRewriteSession rewriteSession, IParseTreeAnnotation annotation, IAnnotation annotationInfo, IReadOnlyList newValues = null) { var newAnnotationValues = newValues ?? new List(); diff --git a/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinder.cs b/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinder.cs index e013722309..5173c9e78b 100644 --- a/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinder.cs +++ b/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinder.cs @@ -14,7 +14,7 @@ public class ConcurrentlyConstructedDeclarationFinder : DeclarationFinder public ConcurrentlyConstructedDeclarationFinder( IReadOnlyList declarations, - IEnumerable annotations, + IEnumerable annotations, IReadOnlyList unresolvedMemberDeclarations, IReadOnlyDictionary> unboundDefaultMemberAccesses, IHostApplication hostApp = null) diff --git a/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinderFactory.cs b/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinderFactory.cs index 0066923f09..1456c20b79 100644 --- a/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinderFactory.cs +++ b/Rubberduck.Parsing/VBA/DeclarationCaching/ConcurrentlyConstructedDeclarationFinderFactory.cs @@ -10,7 +10,7 @@ public class ConcurrentlyConstructedDeclarationFinderFactory : IDeclarationFinde { public DeclarationFinder Create( IReadOnlyList declarations, - IEnumerable annotations, + IEnumerable annotations, IReadOnlyList unresolvedMemberDeclarations, IReadOnlyDictionary> unboundDefaultMemberAccesses, IHostApplication hostApp) diff --git a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs index 2874269307..9e61a1c6ce 100644 --- a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs +++ b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs @@ -28,7 +28,7 @@ public class DeclarationFinder private readonly ConcurrentDictionary> _newUndeclared; private readonly ConcurrentBag _newUnresolved; private List _unresolved; - private IDictionary<(QualifiedModuleName module, int annotatedLine), List> _annotations; + private IDictionary<(QualifiedModuleName module, int annotatedLine), List> _annotations; private IDictionary> _parametersByParent; private IDictionary> _userDeclarationsByType; private IDictionary> _declarationsBySelection; @@ -67,7 +67,7 @@ private static QualifiedSelection GetGroupingKey(Declaration declaration) public DeclarationFinder( IReadOnlyList declarations, - IEnumerable annotations, + IEnumerable annotations, IReadOnlyList unresolvedMemberDeclarations, IReadOnlyDictionary> unboundDefaultMemberAccesses, IHostApplication hostApp = null) @@ -91,7 +91,7 @@ protected virtual void ExecuteCollectionConstructionActions(List collect collectionConstructionActions.ForEach(action => action.Invoke()); } - private List CollectionConstructionActions(IReadOnlyList declarations, IEnumerable annotations, + private List CollectionConstructionActions(IReadOnlyList declarations, IEnumerable annotations, IReadOnlyList unresolvedMemberDeclarations) { var actions = new List @@ -543,25 +543,25 @@ public IEnumerable FindMemberMatches(Declaration parent, string mem : Enumerable.Empty(); } - public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine) + public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine) { return _annotations.TryGetValue((module, annotatedLine), out var result) ? result - : Enumerable.Empty(); + : Enumerable.Empty(); } - public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine, Type annotationType) + public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine, Type annotationType) { return FindAnnotations(module, annotatedLine).Where(pta => pta.Annotation.GetType() == annotationType); } - public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine) + public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine) where T : IAnnotation { return FindAnnotations(module, annotatedLine, typeof(T)); } - public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine, AnnotationTarget target) + public IEnumerable FindAnnotations(QualifiedModuleName module, int annotatedLine, AnnotationTarget target) { return FindAnnotations(module, annotatedLine) .Where(annot => annot.Annotation.Target.HasFlag(target)); diff --git a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinderFactory.cs b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinderFactory.cs index 21f92d2a17..dee72f382a 100644 --- a/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinderFactory.cs +++ b/Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinderFactory.cs @@ -9,7 +9,7 @@ namespace Rubberduck.Parsing.VBA.DeclarationCaching public class DeclarationFinderFactory : IDeclarationFinderFactory { public DeclarationFinder Create(IReadOnlyList declarations, - IEnumerable annotations, + IEnumerable annotations, IReadOnlyList unresolvedMemberDeclarations, IReadOnlyDictionary> unboundDefaultMemberAccesses, IHostApplication hostApp) diff --git a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs index 9aca286ca1..6773efad1a 100644 --- a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs +++ b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunnerBase.cs @@ -175,7 +175,7 @@ protected void ResolveDeclarations(QualifiedModuleName module, IParseTree tree, private ModuleDeclaration NewModuleDeclaration( QualifiedModuleName qualifiedModuleName, IParseTree tree, - IDictionary> annotationsOnWhiteSpaceLines, + IDictionary> annotationsOnWhiteSpaceLines, IDictionary<(string scopeIdentifier, DeclarationType scopeType),Attributes> attributes, Declaration projectDeclaration) { @@ -231,7 +231,7 @@ private static Attributes ModuleAttributes(QualifiedModuleName qualifiedModuleNa return moduleAttributes; } - private static IEnumerable FindModuleAnnotations(IParseTree tree, IDictionary> annotationsOnWhiteSpaceLines) + private static IEnumerable FindModuleAnnotations(IParseTree tree, IDictionary> annotationsOnWhiteSpaceLines) { if (annotationsOnWhiteSpaceLines == null) { diff --git a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs index 209bd69d6d..e39a96cca4 100644 --- a/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs +++ b/Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs @@ -18,7 +18,7 @@ public class DeclarationSymbolsListener : VBAParserBaseListener private Declaration _currentScopeDeclaration; private Declaration _parentDeclaration; - private readonly IDictionary> _annotations; + private readonly IDictionary> _annotations; private readonly IDictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes> _attributes; private readonly IDictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext> _membersAllowingAttributes; @@ -27,7 +27,7 @@ public class DeclarationSymbolsListener : VBAParserBaseListener public DeclarationSymbolsListener( Declaration moduleDeclaration, - IDictionary> annotations, + IDictionary> annotations, IDictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes> attributes, IDictionary<(string scopeIdentifier, DeclarationType scopeType), @@ -42,12 +42,12 @@ public class DeclarationSymbolsListener : VBAParserBaseListener SetCurrentScope(); } - private IEnumerable FindMemberAnnotations(int firstMemberLine) + private IEnumerable FindMemberAnnotations(int firstMemberLine) { return FindAnnotations(firstMemberLine, AnnotationTarget.Member); } - private IEnumerable FindAnnotations(int firstLine, AnnotationTarget requiredTarget) + private IEnumerable FindAnnotations(int firstLine, AnnotationTarget requiredTarget) { if (_annotations == null) { @@ -59,15 +59,15 @@ private IEnumerable FindAnnotations(int firstLine, Annotati return scopedAnnotations.Where(annotation => annotation.Annotation.Target.HasFlag(requiredTarget)); } - return Enumerable.Empty(); + return Enumerable.Empty(); } - private IEnumerable FindVariableAnnotations(int firstVariableLine) + private IEnumerable FindVariableAnnotations(int firstVariableLine) { return FindAnnotations(firstVariableLine, AnnotationTarget.Variable); } - private IEnumerable FindGeneralAnnotations(int firstLine) + private IEnumerable FindGeneralAnnotations(int firstLine) { return FindAnnotations(firstLine, AnnotationTarget.General); } diff --git a/Rubberduck.Parsing/VBA/IAnnotationUpdater.cs b/Rubberduck.Parsing/VBA/IAnnotationUpdater.cs index 76fe8f5256..cd15aff747 100644 --- a/Rubberduck.Parsing/VBA/IAnnotationUpdater.cs +++ b/Rubberduck.Parsing/VBA/IAnnotationUpdater.cs @@ -11,8 +11,8 @@ public interface IAnnotationUpdater void AddAnnotation(IRewriteSession rewriteSession, Declaration declaration, IAnnotation newAnnotation, IReadOnlyList values = null); void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, IAnnotation newAnnotation, IReadOnlyList values = null); void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext context, IAnnotation newAnnotation, IReadOnlyList values = null); - void RemoveAnnotation(IRewriteSession rewriteSession, ParseTreeAnnotation annotation); - void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable annotations); - void UpdateAnnotation(IRewriteSession rewriteSession, ParseTreeAnnotation oldAnnotation, IAnnotation newAnnotation, IReadOnlyList newValues = null); + void RemoveAnnotation(IRewriteSession rewriteSession, IParseTreeAnnotation annotation); + void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable annotations); + void UpdateAnnotation(IRewriteSession rewriteSession, IParseTreeAnnotation oldAnnotation, IAnnotation newAnnotation, IReadOnlyList newValues = null); } } \ No newline at end of file diff --git a/Rubberduck.Parsing/VBA/ModuleState.cs b/Rubberduck.Parsing/VBA/ModuleState.cs index 5bcea77351..f169c0fa73 100644 --- a/Rubberduck.Parsing/VBA/ModuleState.cs +++ b/Rubberduck.Parsing/VBA/ModuleState.cs @@ -21,7 +21,7 @@ public class ModuleState public ParserState State { get; private set; } public int ModuleContentHashCode { get; private set; } public List Comments { get; private set; } - public List Annotations { get; private set; } + public List Annotations { get; private set; } public SyntaxErrorException ModuleException { get; private set; } public IDictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes> ModuleAttributes { get; private set; } public IDictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext> MembersAllowingAttributes { get; private set; } @@ -40,7 +40,7 @@ public ModuleState(ConcurrentDictionary declarations) ModuleContentHashCode = 0; Comments = new List(); - Annotations = new List(); + Annotations = new List(); ModuleException = null; ModuleAttributes = new Dictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes>(); MembersAllowingAttributes = new Dictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext>(); @@ -58,7 +58,7 @@ public ModuleState(ParserState state) State = state; ModuleContentHashCode = 0; Comments = new List(); - Annotations = new List(); + Annotations = new List(); ModuleException = null; ModuleAttributes = new Dictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes>(); MembersAllowingAttributes = new Dictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext>(); @@ -74,7 +74,7 @@ public ModuleState(SyntaxErrorException moduleException) State = ParserState.Error; ModuleContentHashCode = 0; Comments = new List(); - Annotations = new List(); + Annotations = new List(); ModuleException = moduleException; ModuleAttributes = new Dictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes>(); MembersAllowingAttributes = new Dictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext>(); @@ -123,7 +123,7 @@ public ModuleState SetComments(List comments) return this; } - public ModuleState SetAnnotations(List annotations) + public ModuleState SetAnnotations(List annotations) { Annotations = annotations; return this; diff --git a/Rubberduck.Parsing/VBA/Parsing/IModuleParser.cs b/Rubberduck.Parsing/VBA/Parsing/IModuleParser.cs index 33665b1806..82a6f210fe 100644 --- a/Rubberduck.Parsing/VBA/Parsing/IModuleParser.cs +++ b/Rubberduck.Parsing/VBA/Parsing/IModuleParser.cs @@ -14,7 +14,7 @@ namespace Rubberduck.Parsing.VBA.Parsing IParseTree codePaneParseTree, IParseTree attributesParseTree, IEnumerable comments, - IEnumerable annotations, + IEnumerable annotations, IDictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes> attributes, IDictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext> membersAllowingAttributes, ITokenStream codePaneTokenStream, @@ -34,7 +34,7 @@ ITokenStream attributesTokenStream public IParseTree CodePaneParseTree { get; } public IParseTree AttributesParseTree { get; } public IEnumerable Comments { get; } - public IEnumerable Annotations { get; } + public IEnumerable Annotations { get; } public IDictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes> Attributes { get; } public IDictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext> MembersAllowingAttributes { get; } public ITokenStream CodePaneTokenStream { get; } diff --git a/Rubberduck.Parsing/VBA/Parsing/ModuleParser.cs b/Rubberduck.Parsing/VBA/Parsing/ModuleParser.cs index 94966dc98c..633f7cfb54 100644 --- a/Rubberduck.Parsing/VBA/Parsing/ModuleParser.cs +++ b/Rubberduck.Parsing/VBA/Parsing/ModuleParser.cs @@ -119,7 +119,7 @@ private ModuleParseResults ParseInternal(QualifiedModuleName module, Cancellatio } - private (IEnumerable Comments, IEnumerable Annotations) CommentsAndAnnotations(QualifiedModuleName module, IParseTree tree) + private (IEnumerable Comments, IEnumerable Annotations) CommentsAndAnnotations(QualifiedModuleName module, IParseTree tree) { var commentListener = new CommentListener(); var annotationListener = new AnnotationListener(_annotationFactory, module); diff --git a/Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs b/Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs index 3c4e977ab7..814c85d156 100644 --- a/Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs +++ b/Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs @@ -131,7 +131,7 @@ public BoundExpressionVisitor(DeclarationFinder declarationFinder) isSetAssignment); } - private IEnumerable FindIdentifierAnnotations(QualifiedModuleName module, int line) + private IEnumerable FindIdentifierAnnotations(QualifiedModuleName module, int line) { return _declarationFinder.FindAnnotations(module, line, AnnotationTarget.Identifier); } diff --git a/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs b/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs index 8efcc9b61a..de8406d859 100644 --- a/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs +++ b/Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs @@ -160,10 +160,9 @@ private void ResolveLabel(ParserRuleContext context, string label) } } - private IEnumerable FindIdentifierAnnotations(QualifiedModuleName module, int line) + private IEnumerable FindIdentifierAnnotations(QualifiedModuleName module, int line) { - return _declarationFinder.FindAnnotations(module, line) - .Where(annotation => annotation.Annotation.Target.HasFlag(AnnotationTarget.Identifier)); + return _declarationFinder.FindAnnotations(module, line, AnnotationTarget.Identifier); } private void ResolveDefault( diff --git a/Rubberduck.Parsing/VBA/RubberduckParserState.cs b/Rubberduck.Parsing/VBA/RubberduckParserState.cs index d085817c0a..d1d3c5ae8d 100644 --- a/Rubberduck.Parsing/VBA/RubberduckParserState.cs +++ b/Rubberduck.Parsing/VBA/RubberduckParserState.cs @@ -674,11 +674,11 @@ public IReadOnlyCollection GetModuleComments(QualifiedModuleName mo return moduleState.Comments; } - public List AllAnnotations + public List AllAnnotations { get { - var annotations = new List(); + var annotations = new List(); foreach (var state in _moduleStates.Values) { annotations.AddRange(state.Annotations); @@ -688,19 +688,19 @@ public List AllAnnotations } } - public IEnumerable GetModuleAnnotations(QualifiedModuleName module) + public IEnumerable GetModuleAnnotations(QualifiedModuleName module) { if (_moduleStates.TryGetValue(module, out var result)) { return result.Annotations; } - return Enumerable.Empty(); + return Enumerable.Empty(); } - public void SetModuleAnnotations(QualifiedModuleName module, IEnumerable annotations) + public void SetModuleAnnotations(QualifiedModuleName module, IEnumerable annotations) { - _moduleStates[module].SetAnnotations(new List(annotations)); + _moduleStates[module].SetAnnotations(new List(annotations)); } /// diff --git a/Rubberduck.UnitTesting/UnitTesting/TestEngine.cs b/Rubberduck.UnitTesting/UnitTesting/TestEngine.cs index 83b4d88a4a..9d9dc55e90 100644 --- a/Rubberduck.UnitTesting/UnitTesting/TestEngine.cs +++ b/Rubberduck.UnitTesting/UnitTesting/TestEngine.cs @@ -258,7 +258,7 @@ private void RunWhileSuspended(IEnumerable tests) OnTestStarted(test); // no need to run setup/teardown for ignored tests - if (test.Declaration.Annotations.OfType().Any()) + if (test.Declaration.Annotations.Any(a => a.Annotation is IgnoreTestAnnotation)) { OnTestCompleted(test, new TestResult(TestOutcome.Ignored)); continue; diff --git a/Rubberduck.UnitTesting/UnitTesting/TestMethod.cs b/Rubberduck.UnitTesting/UnitTesting/TestMethod.cs index 3138d74597..430e660594 100644 --- a/Rubberduck.UnitTesting/UnitTesting/TestMethod.cs +++ b/Rubberduck.UnitTesting/UnitTesting/TestMethod.cs @@ -40,7 +40,7 @@ public NavigateCodeEventArgs GetNavigationArgs() return new NavigateCodeEventArgs(new QualifiedSelection(Declaration.QualifiedName.QualifiedModuleName, Declaration.Context.GetSelection())); } - public bool IsIgnored => Declaration.Annotations.OfType().Any(); + public bool IsIgnored => Declaration.Annotations.Any(a => a.Annotation is IgnoreTestAnnotation); public bool Equals(TestMethod other) => other != null && Declaration.QualifiedName.Equals(other.Declaration.QualifiedName) && TestCode.Equals(other.TestCode); diff --git a/RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs b/RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs index 0249bc6cc4..97dbc93332 100644 --- a/RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs +++ b/RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs @@ -81,7 +81,7 @@ public void MemberAttributeAnnotationReturnsSpecializedAnnotationsWhereApplicabl private AttributeAnnotationProvider GetAnnotationProvider() { - return new AttributeAnnotationProvider(MockParser.GetWellKnownAnnotations().OfType()); + return new AttributeAnnotationProvider(MockParser.WellKnownAnnotations().OfType()); } private static void AssertEqual(IReadOnlyList expectedList, IReadOnlyList actualList) diff --git a/RubberduckTests/CodeExplorer/CodeExplorerComponentViewModelTests.cs b/RubberduckTests/CodeExplorer/CodeExplorerComponentViewModelTests.cs index bc957ad54c..edbc4f9efd 100644 --- a/RubberduckTests/CodeExplorer/CodeExplorerComponentViewModelTests.cs +++ b/RubberduckTests/CodeExplorer/CodeExplorerComponentViewModelTests.cs @@ -457,7 +457,7 @@ private static Declaration PredeclaredClassDeclaration(Declaration project) project, PredeclaredClassName, true, - Enumerable.Empty(), + Enumerable.Empty(), attributes); } } diff --git a/RubberduckTests/CodeExplorer/CodeExplorerFolderTests.cs b/RubberduckTests/CodeExplorer/CodeExplorerFolderTests.cs index 77d38003bc..d405616893 100644 --- a/RubberduckTests/CodeExplorer/CodeExplorerFolderTests.cs +++ b/RubberduckTests/CodeExplorer/CodeExplorerFolderTests.cs @@ -1,4 +1,5 @@ -using NUnit.Framework; +using Moq; +using NUnit.Framework; using Rubberduck.Navigation.CodeExplorer; using Rubberduck.Parsing.Annotations; using Rubberduck.Parsing.Grammar; @@ -106,16 +107,21 @@ Sub Foo() var folder = (CodeExplorerCustomFolderViewModel)explorer.ViewModel.SelectedItem; var declarations = project.State.AllUserDeclarations.ToList(); - var annotation = new ParseTreeAnnotation(new FolderAnnotation(), new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(1, 1)), new[] { "\"First\"" }); + var mockedAnnotation = new Mock(); + mockedAnnotation.Setup(m => m.Annotation).Returns(new FolderAnnotation()); + mockedAnnotation.Setup(m => m.QualifiedSelection).Returns(new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(1, 1))); + // returns unquoted argument because the FolderAnnotation's argument processing is never invoked in the mock + mockedAnnotation.Setup(m => m.AnnotationArguments).Returns(new[] { "First" }.ToList()); + var annotation = mockedAnnotation.Object; var predeclared = new ParseTreeAnnotation(new PredeclaredIdAnnotation(), new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(2, 1)), (VBAParser.AnnotationContext)null); - declarations.Add(GetNewClassDeclaration(project.Declaration, "Foo", new ParseTreeAnnotation[] { annotation, predeclared })); + declarations.Add(GetNewClassDeclaration(project.Declaration, "Foo", new IParseTreeAnnotation[] { annotation, predeclared })); project.Synchronize(ref declarations); var added = folder.Children.OfType().Single(); Assert.AreEqual(DeclarationType.ClassModule, added.Declaration.DeclarationType); - Assert.AreEqual("\"First\"", added.Declaration.CustomFolder); + Assert.AreEqual("First", added.Declaration.CustomFolder); } } @@ -138,10 +144,15 @@ Sub Foo() var folder = (CodeExplorerCustomFolderViewModel)explorer.ViewModel.SelectedItem; var declarations = project.State.AllUserDeclarations.ToList(); - var annotation = new ParseTreeAnnotation(new FolderAnnotation(), new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(2, 1)), new[] { "First" }); + var mockedAnnotation = new Mock(); + mockedAnnotation.Setup(m => m.Annotation).Returns(new FolderAnnotation()); + mockedAnnotation.Setup(m => m.QualifiedSelection).Returns(new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(2, 1))); + // returns unquoted argument because the FolderAnnotation's argument processing is never invoked in the mock + mockedAnnotation.Setup(m => m.AnnotationArguments).Returns(new[] { "First" }.ToList()); + var annotation = mockedAnnotation.Object; var predeclared = new ParseTreeAnnotation(new PredeclaredIdAnnotation(), new QualifiedSelection(project.Declaration.QualifiedModuleName, new Selection(1, 1)), (VBAParser.AnnotationContext)null); - declarations.Add(GetNewClassDeclaration(project.Declaration, "Foo", new ParseTreeAnnotation[] { predeclared, annotation })); + declarations.Add(GetNewClassDeclaration(project.Declaration, "Foo", new IParseTreeAnnotation[] { predeclared, annotation })); project.Synchronize(ref declarations); var added = folder.Children.OfType().Single(); @@ -356,14 +367,19 @@ public void FoldersNamesAreCaseSensitive() private static Declaration GetNewClassDeclaration(Declaration project, string name, string folder = "") { + var mockedFolderAnnotation = new Mock(); + mockedFolderAnnotation.Setup(m => m.Annotation).Returns(new FolderAnnotation()); + mockedFolderAnnotation.Setup(m => m.AnnotationArguments).Returns(new[] { folder }.ToList()); + mockedFolderAnnotation.Setup(m => m.QualifiedSelection).Returns(new QualifiedSelection(project.QualifiedModuleName, new Selection(1, 1))); + var annotations = string.IsNullOrEmpty(folder) - ? Enumerable.Empty() - : new[] { new ParseTreeAnnotation(new FolderAnnotation(), new QualifiedSelection(project.QualifiedModuleName, new Selection(1, 1)), new[] { folder }) }; + ? Enumerable.Empty() + : new[] { mockedFolderAnnotation.Object }; return GetNewClassDeclaration(project, name, annotations); } - private static Declaration GetNewClassDeclaration(Declaration project, string name, IEnumerable annotations) + private static Declaration GetNewClassDeclaration(Declaration project, string name, IEnumerable annotations) { var declaration = new ClassModuleDeclaration(new QualifiedMemberName(project.QualifiedModuleName, name), project, name, true, annotations, new Attributes()); diff --git a/RubberduckTests/Grammar/AnnotationTests.cs b/RubberduckTests/Grammar/AnnotationTests.cs index 7a60266b73..7115477637 100644 --- a/RubberduckTests/Grammar/AnnotationTests.cs +++ b/RubberduckTests/Grammar/AnnotationTests.cs @@ -1,8 +1,10 @@ using NUnit.Framework; using Rubberduck.Parsing.Annotations; using Rubberduck.VBEditor; +using RubberduckTests.Mocks; using System; using System.Collections.Generic; +using System.Linq; namespace RubberduckTests.Grammar { @@ -41,6 +43,24 @@ public void AnnotationTypes_MatchExpectedAnnotationNames(Type annotationType, st Assert.AreEqual(expectedName, annotation.Name); } + [TestCase] + public void AnnotationTypes_AllHave_SomeName() + { + foreach (var annotation in MockParser.WellKnownAnnotations()) + { + Assert.IsNotEmpty(annotation.Name); + } + } + + [TestCase] + public void AnnotationTypes_HaveDistinctNames() + { + var annotations = MockParser.WellKnownAnnotations(); + var names = annotations.Select(a => a.Name).Distinct(); + + Assert.AreEqual(annotations.Count(), names.Count()); + } + [TestCase(typeof(IgnoreAnnotation))] [TestCase(typeof(IgnoreModuleAnnotation))] public void AnnotationTypes_MultipleApplicationsAllowed(Type annotationType) diff --git a/RubberduckTests/Inspections/AttributeValueOutOfSyncInspectionTests.cs b/RubberduckTests/Inspections/AttributeValueOutOfSyncInspectionTests.cs index 0254dfb1d2..503e0a9c2f 100644 --- a/RubberduckTests/Inspections/AttributeValueOutOfSyncInspectionTests.cs +++ b/RubberduckTests/Inspections/AttributeValueOutOfSyncInspectionTests.cs @@ -218,10 +218,12 @@ public void ResultContainsAnnotationAndAttributeValues() var inspectionResults = InspectionResults(inputCode); var inspectionResult = inspectionResults.First(); - - Assert.IsInstanceOf(inspectionResult.Properties.Annotation.Annotation); + + var pta = (IParseTreeAnnotation)inspectionResult.Properties.Annotation; + + Assert.IsInstanceOf(pta.Annotation); Assert.AreEqual("VB_UserMemId", inspectionResult.Properties.AttributeName); - Assert.AreEqual("-4", ((ParseTreeAnnotation)inspectionResult.Properties.Annotation).AttributeValues()[0]); + Assert.AreEqual("-4", ((IAttributeAnnotation)pta.Annotation).AttributeValues(pta)[0]); Assert.AreEqual("40", inspectionResult.Properties.AttributeValues[0]); } diff --git a/RubberduckTests/Inspections/InspectionResultTests.cs b/RubberduckTests/Inspections/InspectionResultTests.cs index 54eb562fa4..c35f942603 100644 --- a/RubberduckTests/Inspections/InspectionResultTests.cs +++ b/RubberduckTests/Inspections/InspectionResultTests.cs @@ -140,7 +140,7 @@ public void IdentifierRefereneceInspectionResultsAreDeemedInvalidatedIfTheModule var modifiedModules = new HashSet { declarationModule }; var declarationFinderProviderMock = new Mock(); - var declaratioFinder = new DeclarationFinder(new List(), new List(), + var declaratioFinder = new DeclarationFinder(new List(), new List(), new List(), new Dictionary>()); declarationFinderProviderMock.SetupGet(m => m.DeclarationFinder).Returns(declaratioFinder); var inspectionResult = new IdentifierReferenceInspectionResult(inspectionMock.Object, string.Empty, declarationFinderProviderMock.Object, identifierReference); @@ -169,7 +169,7 @@ public void IdentifierReferenceInspectionResultsAreNotDeemedInvalidatedIfNeither var modifiedModules = new HashSet { otherModule }; var declarationFinderProviderMock = new Mock(); - var declaratioFinder = new DeclarationFinder(new List(), new List(), + var declaratioFinder = new DeclarationFinder(new List(), new List(), new List(), new Dictionary>()); declarationFinderProviderMock.SetupGet(m => m.DeclarationFinder).Returns(declaratioFinder); var inspectionResult = new IdentifierReferenceInspectionResult(inspectionMock.Object, string.Empty, declarationFinderProviderMock.Object, identifierReference); diff --git a/RubberduckTests/Inspections/UntypedFunctionUsageInspectionTests.cs b/RubberduckTests/Inspections/UntypedFunctionUsageInspectionTests.cs index 43862cbde3..5ff4609aa0 100644 --- a/RubberduckTests/Inspections/UntypedFunctionUsageInspectionTests.cs +++ b/RubberduckTests/Inspections/UntypedFunctionUsageInspectionTests.cs @@ -143,7 +143,7 @@ private List GetBuiltInDeclarations() vbaDeclaration, "Conversion", false, - new List(), + new List(), new Attributes()); var fileSystemModule = new ProceduralModuleDeclaration( @@ -151,7 +151,7 @@ private List GetBuiltInDeclarations() vbaDeclaration, "FileSystem", false, - new List(), + new List(), new Attributes()); var interactionModule = new ProceduralModuleDeclaration( @@ -159,7 +159,7 @@ private List GetBuiltInDeclarations() vbaDeclaration, "Interaction", false, - new List(), + new List(), new Attributes()); var stringsModule = new ProceduralModuleDeclaration( @@ -167,7 +167,7 @@ private List GetBuiltInDeclarations() vbaDeclaration, "Strings", false, - new List(), + new List(), new Attributes()); var dateTimeModule = new ProceduralModuleDeclaration( @@ -175,7 +175,7 @@ private List GetBuiltInDeclarations() vbaDeclaration, "Strings", false, - new List(), + new List(), new Attributes()); var hiddenModule = new ProceduralModuleDeclaration( @@ -183,7 +183,7 @@ private List GetBuiltInDeclarations() vbaDeclaration, "_HiddenModule", false, - new List(), + new List(), new Attributes()); @@ -200,7 +200,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var environFunction = new FunctionDeclaration( @@ -216,7 +216,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var rtrimFunction = new FunctionDeclaration( @@ -232,7 +232,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var chrFunction = new FunctionDeclaration( @@ -248,7 +248,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var formatFunction = new FunctionDeclaration( @@ -264,7 +264,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstFormatParam = new ParameterDeclaration( @@ -311,7 +311,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstRightParam = new ParameterDeclaration( @@ -338,7 +338,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var leftbFunction = new FunctionDeclaration( @@ -354,7 +354,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstLeftBParam = new ParameterDeclaration( @@ -381,7 +381,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var leftFunction = new FunctionDeclaration( @@ -397,7 +397,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstLeftParam = new ParameterDeclaration( @@ -424,7 +424,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstRightBParam = new ParameterDeclaration( @@ -451,7 +451,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstMidBParam = new ParameterDeclaration( @@ -488,7 +488,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var trimFunction = new FunctionDeclaration( @@ -504,7 +504,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var ltrimFunction = new FunctionDeclaration( @@ -520,7 +520,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var midFunction = new FunctionDeclaration( @@ -536,7 +536,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstMidParam = new ParameterDeclaration( @@ -573,7 +573,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var octFunction = new FunctionDeclaration( @@ -589,7 +589,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var errorFunction = new FunctionDeclaration( @@ -605,7 +605,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var strFunction = new FunctionDeclaration( @@ -621,7 +621,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var curDirFunction = new FunctionDeclaration( @@ -637,7 +637,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var datePropertyGet = new PropertyGetDeclaration( @@ -653,7 +653,7 @@ private List GetBuiltInDeclarations() new Selection(), false, false, - new List(), + new List(), new Attributes()); @@ -670,7 +670,7 @@ private List GetBuiltInDeclarations() new Selection(), false, false, - new List(), + new List(), new Attributes()); var inputbFunction = new FunctionDeclaration( @@ -686,7 +686,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstInputBParam = new ParameterDeclaration( @@ -723,7 +723,7 @@ private List GetBuiltInDeclarations() Selection.Home, false, false, - new List(), + new List(), new Attributes()); var firstInputParam = new ParameterDeclaration( diff --git a/RubberduckTests/Mocks/MockParser.cs b/RubberduckTests/Mocks/MockParser.cs index aac9ea2363..222fb32f19 100644 --- a/RubberduckTests/Mocks/MockParser.cs +++ b/RubberduckTests/Mocks/MockParser.cs @@ -76,7 +76,7 @@ public static (SynchronousParseCoordinator parser, IRewritingManager rewritingMa var mainTokenStreamParser = new VBATokenStreamParser(mainParseErrorListenerFactory, mainParseErrorListenerFactory); var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider(); var stringParser = new TokenStreamParserStringParserAdapterWithPreprocessing(tokenStreamProvider, mainTokenStreamParser, preprocessor); - var vbaParserAnnotationFactory = new VBAParserAnnotationFactory(GetWellKnownAnnotations()); + var vbaParserAnnotationFactory = new VBAParserAnnotationFactory(WellKnownAnnotations()); var projectManager = new RepositoryProjectManager(projectRepository); var moduleToModuleReferenceManager = new ModuleToModuleReferenceManager(); var supertypeClearer = new SynchronousSupertypeClearer(state); @@ -162,7 +162,7 @@ public static (SynchronousParseCoordinator parser, IRewritingManager rewritingMa return (parser, rewritingManager); } - public static IEnumerable GetWellKnownAnnotations() + public static IEnumerable WellKnownAnnotations() { return Assembly.GetAssembly(typeof(IAnnotation)) .GetTypes() diff --git a/RubberduckTests/QuickFixes/AddAttributeAnnotationQuickFixTests.cs b/RubberduckTests/QuickFixes/AddAttributeAnnotationQuickFixTests.cs index 7c6b05e608..e69a0b2b8f 100644 --- a/RubberduckTests/QuickFixes/AddAttributeAnnotationQuickFixTests.cs +++ b/RubberduckTests/QuickFixes/AddAttributeAnnotationQuickFixTests.cs @@ -156,9 +156,8 @@ public void KnownMemberAttributeWithoutAnnotationWhileOtherAttributeWithAnnotati protected override IQuickFix QuickFix(RubberduckParserState state) { - // FIXME actually inject the annotations here... return new AddAttributeAnnotationQuickFix(new AnnotationUpdater(), - new AttributeAnnotationProvider(MockParser.GetWellKnownAnnotations().OfType())); + new AttributeAnnotationProvider(MockParser.WellKnownAnnotations().OfType())); } } } \ No newline at end of file diff --git a/RubberduckTests/QuickFixes/AdjustAttributeAnnotationQuickFixTests.cs b/RubberduckTests/QuickFixes/AdjustAttributeAnnotationQuickFixTests.cs index c57833bad9..363b0621dd 100644 --- a/RubberduckTests/QuickFixes/AdjustAttributeAnnotationQuickFixTests.cs +++ b/RubberduckTests/QuickFixes/AdjustAttributeAnnotationQuickFixTests.cs @@ -110,7 +110,7 @@ protected override IVBE TestVbe(string code, out IVBComponent component) protected override IQuickFix QuickFix(RubberduckParserState state) { return new AdjustAttributeAnnotationQuickFix(new AnnotationUpdater(), - new AttributeAnnotationProvider(MockParser.GetWellKnownAnnotations().OfType())); + new AttributeAnnotationProvider(MockParser.WellKnownAnnotations().OfType())); } } } \ No newline at end of file diff --git a/RubberduckTests/QuickFixes/RemoveDuplicatedAnnotationQuickFixTests.cs b/RubberduckTests/QuickFixes/RemoveDuplicatedAnnotationQuickFixTests.cs index 195446c4c2..7fd4bc1510 100644 --- a/RubberduckTests/QuickFixes/RemoveDuplicatedAnnotationQuickFixTests.cs +++ b/RubberduckTests/QuickFixes/RemoveDuplicatedAnnotationQuickFixTests.cs @@ -182,7 +182,7 @@ public void RemoveDuplicatedAnnotation_QuickFixWorks_RemoveDuplicatesOfOnlyOneAn '@TestMethod Public Sub Foo End Sub"; - Func conditionToFix = result => result.Properties.AnnotationType is ObsoleteAnnotation; + Func conditionToFix = result => result.Properties.Annotation is ObsoleteAnnotation; var actualCode = ApplyQuickFixToFirstInspectionResultSatisfyingPredicate(inputCode, state => new DuplicatedAnnotationInspection(state), conditionToFix); Assert.AreEqual(expectedCode, actualCode); } diff --git a/RubberduckTests/Refactoring/Rename/RenameTests.cs b/RubberduckTests/Refactoring/Rename/RenameTests.cs index 458fa59267..904ff96f16 100644 --- a/RubberduckTests/Refactoring/Rename/RenameTests.cs +++ b/RubberduckTests/Refactoring/Rename/RenameTests.cs @@ -803,8 +803,8 @@ End Sub public void RenamePresenter_WarnsAboutControlEventHandlerRename_AbortsOnDeniedConfirmation() { var qmn = new QualifiedModuleName("TestProject", string.Empty, "TestComponent"); - var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); - var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); var model = new RenameModel(originalTargetDeclaration) { @@ -822,8 +822,8 @@ public void RenamePresenter_WarnsAboutControlEventHandlerRename_AbortsOnDeniedCo public void RenamePresenter_WarnsAboutControlEventHandlerRename_ContinuesAfterConfirmation() { var qmn = new QualifiedModuleName("TestProject", string.Empty, "TestComponent"); - var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); - var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); var model = new RenameModel(originalTargetDeclaration) { @@ -1232,8 +1232,8 @@ End Sub public void RenamePresenter_WarnsAboutEventHandlerRename_AbortsOnDeniedConfirmation() { var qmn = new QualifiedModuleName("TestProject", string.Empty, "TestComponent"); - var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); - var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); var model = new RenameModel(originalTargetDeclaration) { @@ -1251,8 +1251,8 @@ public void RenamePresenter_WarnsAboutEventHandlerRename_AbortsOnDeniedConfirmat public void RenamePresenter_WarnsAboutEventHandlerRename_ContinuesAfterConfirmation() { var qmn = new QualifiedModuleName("TestProject", string.Empty, "TestComponent"); - var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); - var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); var model = new RenameModel(originalTargetDeclaration) { @@ -1501,8 +1501,8 @@ End Sub public void RenamePresenter_WarnsAboutInterfaceVariableImplementationRename_AbortsOnDeniedConfirmation() { var qmn = new QualifiedModuleName("TestProject", string.Empty, "TestComponent"); - var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn,"Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); - var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn,"Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); var model = new RenameModel(originalTargetDeclaration) { @@ -1520,8 +1520,8 @@ public void RenamePresenter_WarnsAboutInterfaceVariableImplementationRename_Abor public void RenamePresenter_WarnsAboutInterfaceVariableImplementationRename_ContinuesAfterConfirmation() { var qmn = new QualifiedModuleName("TestProject", string.Empty, "TestComponent"); - var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); - var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var testDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Foo"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); + var originalTargetDeclaration = new FunctionDeclaration(new QualifiedMemberName(qmn, "Bar"), null, null, "Variant", null, string.Empty, Accessibility.Public, null, null, Selection.Home, false, true, Enumerable.Empty(), null); var model = new RenameModel(originalTargetDeclaration) { diff --git a/RubberduckTests/Symbols/DeclarationFinderTests.cs b/RubberduckTests/Symbols/DeclarationFinderTests.cs index a92fa0562b..76f324e043 100644 --- a/RubberduckTests/Symbols/DeclarationFinderTests.cs +++ b/RubberduckTests/Symbols/DeclarationFinderTests.cs @@ -2122,7 +2122,7 @@ private static FunctionDeclaration GetTestFunction(Declaration moduleDeclatation private static void AddReference(Declaration toDeclaration, Declaration fromModuleDeclaration, ParserRuleContext context = null) { - toDeclaration.AddReference(toDeclaration.QualifiedName.QualifiedModuleName, fromModuleDeclaration, fromModuleDeclaration, context, toDeclaration.IdentifierName, toDeclaration, Selection.Home, new List()); + toDeclaration.AddReference(toDeclaration.QualifiedName.QualifiedModuleName, fromModuleDeclaration, fromModuleDeclaration, context, toDeclaration.IdentifierName, toDeclaration, Selection.Home, new List()); } } } \ No newline at end of file From 5a5e07008352d6cc90f94e13bf9cf827ab4c974a Mon Sep 17 00:00:00 2001 From: Vogel612 Date: Fri, 6 Sep 2019 21:53:01 +0200 Subject: [PATCH 4/4] Correct IAnnotationFactory registration --- .../QuickFixes/AdjustAttributeValuesQuickFix.cs | 4 +++- Rubberduck.Main/Root/RubberduckIoCInstaller.cs | 4 ++++ 2 files changed, 7 insertions(+), 1 deletion(-) diff --git a/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeValuesQuickFix.cs b/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeValuesQuickFix.cs index 04c835cc9d..9bf9f0d43e 100644 --- a/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeValuesQuickFix.cs +++ b/Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeValuesQuickFix.cs @@ -1,5 +1,6 @@ using System; using System.Collections.Generic; +using System.Diagnostics; using Rubberduck.Inspections.Abstract; using Rubberduck.Inspections.Concrete; using Rubberduck.Parsing.Annotations; @@ -25,7 +26,8 @@ public override void Fix(IInspectionResult result, IRewriteSession rewriteSessio { var declaration = result.Target; IParseTreeAnnotation annotationInstance = result.Properties.Annotation; - // FIXME consider dealing with the implicit assumption here? + + Debug.Assert(annotationInstance.Annotation is IAttributeAnnotation); IAttributeAnnotation annotation = (IAttributeAnnotation)annotationInstance.Annotation; IReadOnlyList attributeValues = result.Properties.AttributeValues; diff --git a/Rubberduck.Main/Root/RubberduckIoCInstaller.cs b/Rubberduck.Main/Root/RubberduckIoCInstaller.cs index e9f887189d..d455529997 100644 --- a/Rubberduck.Main/Root/RubberduckIoCInstaller.cs +++ b/Rubberduck.Main/Root/RubberduckIoCInstaller.cs @@ -304,6 +304,7 @@ private void RegisterFactories(IWindsorContainer container, Assembly[] assemblie .Where(type => type.IsInterface && type.Name.EndsWith("Factory") && !type.Name.Equals("IFakesFactory") + && !type.Name.Equals("IAnnotationFactory") && type.NotDisabledOrExperimental(_initialSettings)) .WithService.Self() .Configure(c => c.AsFactory()) @@ -957,6 +958,9 @@ private void RegisterAnnotationProcessing(IWindsorContainer container) .WithServiceAllInterfaces() .LifestyleSingleton()); } + container.Register(Component.For() + .ImplementedBy() + .LifestyleSingleton()); } private void RegisterTypeLibApi(IWindsorContainer container)