Skip to content

Commit d865e3d

Browse files
committed
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.
1 parent 40d4d24 commit d865e3d

File tree

86 files changed

+661
-753
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

86 files changed

+661
-753
lines changed

Rubberduck.API/VBA/Parser.cs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@
2525
using Rubberduck.Root;
2626
using Rubberduck.VBEditor.ComManagement.TypeLibs;
2727
using Rubberduck.VBEditor.SourceCodeHandling;
28+
using Rubberduck.Parsing.Annotations;
2829

2930
namespace Rubberduck.API.VBA
3031
{
@@ -106,6 +107,8 @@ internal Parser(object vbe) : this()
106107
var preprocessorErrorListenerFactory = new PreprocessingParseErrorListenerFactory();
107108
var preprocessorParser = new VBAPreprocessorParser(preprocessorErrorListenerFactory, preprocessorErrorListenerFactory);
108109
var preprocessor = new VBAPreprocessor(preprocessorParser, compilationsArgumentsCache);
110+
// FIXME inject annotation types to allow Rubberduck api users to access Annotations from VBA code
111+
var annotationProcessor = new VBAParserAnnotationFactory(new List<Type>());
109112
var mainParseErrorListenerFactory = new MainParseErrorListenerFactory();
110113
var mainTokenStreamParser = new VBATokenStreamParser(mainParseErrorListenerFactory, mainParseErrorListenerFactory);
111114
var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider();
@@ -139,7 +142,8 @@ internal Parser(object vbe) : this()
139142
var moduleParser = new ModuleParser(
140143
codePaneSourceCodeHandler,
141144
attributesSourceCodeHandler,
142-
stringParser);
145+
stringParser,
146+
annotationProcessor);
143147
var parseRunner = new ParseRunner(
144148
_state,
145149
parserStateManager,

Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ public AttributeValueOutOfSyncInspection(RubberduckParserState state)
4949
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5050
{
5151
var declarationsWithAttributeAnnotations = State.DeclarationFinder.AllUserDeclarations
52-
.Where(declaration => declaration.Annotations.Any(annotation => annotation.AnnotationType.HasFlag(AnnotationType.Attribute)));
52+
.Where(declaration => declaration.Annotations.Any(annotation => annotation is IAttributeAnnotation));
5353
var results = new List<DeclarationInspectionResult>();
5454
foreach (var declaration in declarationsWithAttributeAnnotations.Where(decl => decl.QualifiedModuleName.ComponentType != ComponentType.Document))
5555
{

Rubberduck.CodeAnalysis/Inspections/Concrete/DuplicatedAnnotationInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -46,8 +46,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4646
foreach (var declaration in State.AllUserDeclarations)
4747
{
4848
var duplicateAnnotations = declaration.Annotations
49-
.GroupBy(annotation => annotation.AnnotationType)
50-
.Where(group => !group.First().AllowMultiple && group.Count() > 1);
49+
.GroupBy(annotation => annotation.GetType())
50+
.Where(group => !group.First().MetaInformation.AllowMultiple && group.Count() > 1);
5151

5252
issues.AddRange(duplicateAnnotations.Select(duplicate =>
5353
{

Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5252
var annotations = State.AllAnnotations;
5353

5454
var unboundAnnotations = UnboundAnnotations(annotations, userDeclarations, identifierReferences)
55-
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.GeneralAnnotation)
55+
.Where(annotation => !annotation.MetaInformation.Target.HasFlag(AnnotationTarget.General)
5656
|| annotation.AnnotatedLine == null);
5757
var attributeAnnotationsInDocuments = AttributeAnnotationsInDocuments(userDeclarations);
5858

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -48,10 +48,12 @@ public MissingAnnotationArgumentInspection(RubberduckParserState state)
4848

4949
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5050
{
51+
// FIXME don't actually use listeners here, iterate the Annotations instead
52+
// FIXME don't maintain a separate list for annotations that require arguments, instead use AnnotationAttribute to store that information
5153
return (from result in Listener.Contexts
5254
let context = (VBAParser.AnnotationContext)result.Context
53-
where context.annotationName().GetText() == AnnotationType.Ignore.ToString()
54-
|| context.annotationName().GetText() == AnnotationType.Folder.ToString()
55+
where context.annotationName().GetText() == "Ignore"
56+
|| context.annotationName().GetText() == "Folder"
5557
where context.annotationArgList() == null
5658
select new QualifiedContextInspectionResult(this,
5759
string.Format(InspectionResults.MissingAnnotationArgumentInspection,

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ public MissingAttributeInspection(RubberduckParserState state)
4848
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4949
{
5050
var declarationsWithAttributeAnnotations = State.DeclarationFinder.AllUserDeclarations
51-
.Where(declaration => declaration.Annotations.Any(annotation => annotation.AnnotationType.HasFlag(AnnotationType.Attribute)));
51+
.Where(declaration => declaration.Annotations.Any(annotation => annotation is IAttributeAnnotation));
5252
var results = new List<DeclarationInspectionResult>();
5353
foreach (var declaration in declarationsWithAttributeAnnotations.Where(decl => decl.QualifiedModuleName.ComponentType != ComponentType.Document
5454
&& !decl.IsIgnoringInspectionResultFor(AnnotationName)))

Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,7 @@ public ModuleWithoutFolderInspection(RubberduckParserState state)
3939
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4040
{
4141
var modulesWithoutFolderAnnotation = State.DeclarationFinder.UserDeclarations(Parsing.Symbols.DeclarationType.Module)
42-
.Where(w => w.Annotations.All(a => a.AnnotationType != AnnotationType.Folder))
42+
.Where(w => !w.Annotations.OfType<FolderAnnotation>().Any())
4343
.ToList();
4444

4545
return modulesWithoutFolderAnnotation

Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -58,15 +58,13 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5858
{
5959
var declarations = State.AllUserDeclarations
6060
.Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Member) &&
61-
declaration.Annotations.Any(annotation =>annotation.AnnotationType == AnnotationType.Obsolete));
61+
declaration.Annotations.OfType<ObsoleteAnnotation>().Any());
6262

6363
var issues = new List<IdentifierReferenceInspectionResult>();
6464

6565
foreach (var declaration in declarations)
6666
{
67-
var replacementDocumentation =
68-
((ObsoleteAnnotation) declaration.Annotations.First(annotation =>
69-
annotation.AnnotationType == AnnotationType.Obsolete)).ReplacementDocumentation;
67+
var replacementDocumentation = declaration.Annotations.OfType<ObsoleteAnnotation>().First().ReplacementDocumentation;
7068

7169
issues.AddRange(declaration.References.Select(reference =>
7270
new IdentifierReferenceInspectionResult(this,

Rubberduck.CodeAnalysis/QuickFixes/AdjustAttributeAnnotationQuickFix.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -39,15 +39,15 @@ public override void Fix(IInspectionResult result, IRewriteSession rewriteSessio
3939
}
4040
else
4141
{
42-
var (newAnnotationType, newAnnotationValues) = _attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues);
43-
_annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotationType, newAnnotationValues);
42+
var (newAnnotation, newAnnotationValues) = _attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues);
43+
_annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotation, newAnnotationValues);
4444
}
4545
}
4646
else
4747
{
4848
var attributeBaseName = AttributeBaseName(attributeName, declaration);
49-
var (newAnnotationType, newAnnotationValues) = _attributeAnnotationProvider.MemberAttributeAnnotation(attributeBaseName, attributeValues);
50-
_annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotationType, newAnnotationValues);
49+
var (newAnnotation, newAnnotationValues) = _attributeAnnotationProvider.MemberAttributeAnnotation(attributeBaseName, attributeValues);
50+
_annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotation, newAnnotationValues);
5151
}
5252
}
5353

Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -52,17 +52,17 @@ private void FixNonModule(IInspectionResult result, IRewriteSession rewriteSessi
5252
.OfType<IgnoreAnnotation>()
5353
.FirstOrDefault();
5454

55-
var annotationType = AnnotationType.Ignore;
55+
var annotationInfo = typeof(IgnoreAnnotation).GetCustomAttributes(false).OfType<AnnotationAttribute>().Single();
5656
if (existingIgnoreAnnotation != null)
5757
{
5858
var annotationValues = existingIgnoreAnnotation.InspectionNames.ToList();
5959
annotationValues.Insert(0, result.Inspection.AnnotationName);
60-
_annotationUpdater.UpdateAnnotation(rewriteSession, existingIgnoreAnnotation, annotationType, annotationValues);
60+
_annotationUpdater.UpdateAnnotation(rewriteSession, existingIgnoreAnnotation, annotationInfo, annotationValues);
6161
}
6262
else
6363
{
6464
var annotationValues = new List<string> { result.Inspection.AnnotationName };
65-
_annotationUpdater.AddAnnotation(rewriteSession, new QualifiedContext(module, result.Context), annotationType, annotationValues);
65+
_annotationUpdater.AddAnnotation(rewriteSession, new QualifiedContext(module, result.Context), annotationInfo, annotationValues);
6666
}
6767
}
6868

@@ -73,7 +73,7 @@ private void FixModule(IInspectionResult result, IRewriteSession rewriteSession)
7373
.OfType<IgnoreModuleAnnotation>()
7474
.FirstOrDefault();
7575

76-
var annotationType = AnnotationType.IgnoreModule;
76+
var annotationType = typeof(IgnoreModuleAnnotation).GetCustomAttributes(false).OfType<AnnotationAttribute>().Single();
7777
if (existingIgnoreModuleAnnotation != null)
7878
{
7979
var annotationValues = existingIgnoreModuleAnnotation.InspectionNames.ToList();

0 commit comments

Comments
 (0)