Skip to content

Commit 5ac876e

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

File tree

116 files changed

+711
-822
lines changed

Some content is hidden

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

116 files changed

+711
-822
lines changed

Rubberduck.API/VBA/Parser.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -107,8 +107,8 @@ internal Parser(object vbe) : this()
107107
var preprocessorErrorListenerFactory = new PreprocessingParseErrorListenerFactory();
108108
var preprocessorParser = new VBAPreprocessorParser(preprocessorErrorListenerFactory, preprocessorErrorListenerFactory);
109109
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>());
110+
// FIXME inject annotations to allow Rubberduck api users to access Annotations from VBA code
111+
var annotationProcessor = new VBAParserAnnotationFactory(new List<IAnnotation>());
112112
var mainParseErrorListenerFactory = new MainParseErrorListenerFactory();
113113
var mainTokenStreamParser = new VBATokenStreamParser(mainParseErrorListenerFactory, mainParseErrorListenerFactory);
114114
var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider();

Rubberduck.CodeAnalysis/Inspections/Concrete/AttributeValueOutOfSyncInspection.cs

Lines changed: 16 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -49,23 +49,26 @@ 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 is IAttributeAnnotation));
52+
.Where(declaration => declaration.Annotations.Any(pta => pta.Annotation is IAttributeAnnotation));
5353
var results = new List<DeclarationInspectionResult>();
5454
foreach (var declaration in declarationsWithAttributeAnnotations.Where(decl => decl.QualifiedModuleName.ComponentType != ComponentType.Document))
5555
{
56-
foreach (var annotation in declaration.Annotations.OfType<IAttributeAnnotation>())
56+
foreach (var annotationInstance in declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation))
5757
{
58-
if (HasDifferingAttributeValues(declaration, annotation, out var attributeValues))
58+
var annotation = annotationInstance.Annotation;
59+
if (HasDifferingAttributeValues(declaration, annotationInstance, out var attributeValues))
5960
{
61+
var attributeName = annotationInstance.Attribute();
62+
6063
var description = string.Format(InspectionResults.AttributeValueOutOfSyncInspection,
61-
annotation.Attribute,
64+
attributeName,
6265
string.Join(", ", attributeValues),
63-
annotation.AnnotationType);
66+
annotation.Name);
6467

6568
var result = new DeclarationInspectionResult(this, description, declaration,
66-
new QualifiedContext(declaration.QualifiedModuleName, annotation.Context));
67-
result.Properties.Annotation = annotation;
68-
result.Properties.AttributeName = annotation.Attribute;
69+
new QualifiedContext(declaration.QualifiedModuleName, annotationInstance.Context));
70+
result.Properties.Annotation = annotationInstance;
71+
result.Properties.AttributeName = attributeName;
6972
result.Properties.AttributeValues = attributeValues;
7073

7174
results.Add(result);
@@ -76,16 +79,17 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
7679
return results;
7780
}
7881

79-
private static bool HasDifferingAttributeValues(Declaration declaration, IAttributeAnnotation annotation, out IReadOnlyList<string> attributeValues)
82+
private static bool HasDifferingAttributeValues(Declaration declaration, ParseTreeAnnotation annotationInstance, out IReadOnlyList<string> attributeValues)
8083
{
84+
var attribute = annotationInstance.Attribute();
8185
var attributeNodes = declaration.DeclarationType.HasFlag(DeclarationType.Module)
82-
? declaration.Attributes.AttributeNodesFor(annotation)
83-
: declaration.Attributes.AttributeNodesFor(annotation, declaration.IdentifierName);
86+
? declaration.Attributes.AttributeNodesFor(annotationInstance)
87+
: declaration.Attributes.AttributeNodesFor(annotationInstance, declaration.IdentifierName);
8488

8589
foreach (var attributeNode in attributeNodes)
8690
{
8791
var values = attributeNode.Values;
88-
if (!annotation.AttributeValues.SequenceEqual(values))
92+
if (!annotationInstance.AttributeValues().SequenceEqual(values))
8993
{
9094
attributeValues = values;
9195
return true;

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.GetType())
50-
.Where(group => !group.First().MetaInformation.AllowMultiple && group.Count() > 1);
49+
.GroupBy(pta => pta.Annotation)
50+
.Where(group => !group.First().Annotation.AllowMultiple && group.Count() > 1);
5151

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

Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs

Lines changed: 4 additions & 4 deletions
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.MetaInformation.Target.HasFlag(AnnotationTarget.General)
55+
.Where(annotation => !annotation.Annotation.Target.HasFlag(AnnotationTarget.General)
5656
|| annotation.AnnotatedLine == null);
5757
var attributeAnnotationsInDocuments = AttributeAnnotationsInDocuments(userDeclarations);
5858

@@ -65,7 +65,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
6565
new QualifiedContext(annotation.QualifiedSelection.QualifiedName, annotation.Context)));
6666
}
6767

68-
private static IEnumerable<IAnnotation> UnboundAnnotations(IEnumerable<IAnnotation> annotations, IEnumerable<Declaration> userDeclarations, IEnumerable<IdentifierReference> identifierReferences)
68+
private static IEnumerable<ParseTreeAnnotation> UnboundAnnotations(IEnumerable<ParseTreeAnnotation> annotations, IEnumerable<Declaration> userDeclarations, IEnumerable<IdentifierReference> identifierReferences)
6969
{
7070
var boundAnnotationsSelections = userDeclarations
7171
.SelectMany(declaration => declaration.Annotations)
@@ -76,11 +76,11 @@ private static IEnumerable<IAnnotation> UnboundAnnotations(IEnumerable<IAnnotati
7676
return annotations.Where(annotation => !boundAnnotationsSelections.Contains(annotation.QualifiedSelection)).ToList();
7777
}
7878

79-
private static IEnumerable<IAnnotation> AttributeAnnotationsInDocuments(IEnumerable<Declaration> userDeclarations)
79+
private static IEnumerable<ParseTreeAnnotation> AttributeAnnotationsInDocuments(IEnumerable<Declaration> userDeclarations)
8080
{
8181
var declarationsInDocuments = userDeclarations
8282
.Where(declaration => declaration.QualifiedModuleName.ComponentType == ComponentType.Document);
83-
return declarationsInDocuments.SelectMany(doc => doc.Annotations).OfType<IAttributeAnnotation>();
83+
return declarationsInDocuments.SelectMany(doc => doc.Annotations).Where(pta => pta.Annotation is IAttributeAnnotation);
8484
}
8585
}
8686
}

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs

Lines changed: 10 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -48,21 +48,21 @@ 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 is IAttributeAnnotation));
51+
.Where(declaration => declaration.Annotations.Any(pta => pta.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)))
5555
{
56-
foreach(var annotation in declaration.Annotations.OfType<IAttributeAnnotation>())
56+
foreach (var annotationInstance in declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation))
5757
{
58-
if (MissesCorrespondingAttribute(declaration, annotation))
58+
var annotation = (IAttributeAnnotation)annotationInstance.Annotation;
59+
if (MissesCorrespondingAttribute(declaration, annotationInstance))
5960
{
60-
var description = string.Format(InspectionResults.MissingAttributeInspection, declaration.IdentifierName,
61-
annotation.AnnotationType.ToString());
61+
var description = string.Format(InspectionResults.MissingAttributeInspection, declaration.IdentifierName, annotation.Name);
6262

6363
var result = new DeclarationInspectionResult(this, description, declaration,
64-
new QualifiedContext(declaration.QualifiedModuleName, annotation.Context));
65-
result.Properties.Annotation = annotation;
64+
new QualifiedContext(declaration.QualifiedModuleName, annotationInstance.Context));
65+
result.Properties.Annotation = annotationInstance;
6666

6767
results.Add(result);
6868
}
@@ -72,9 +72,10 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
7272
return results;
7373
}
7474

75-
private static bool MissesCorrespondingAttribute(Declaration declaration, IAttributeAnnotation annotation)
75+
private static bool MissesCorrespondingAttribute(Declaration declaration, ParseTreeAnnotation annotation)
7676
{
77-
if (string.IsNullOrEmpty(annotation.Attribute))
77+
var attribute = annotation.Attribute();
78+
if (string.IsNullOrEmpty(attribute))
7879
{
7980
return false;
8081
}

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -88,16 +88,15 @@ private static bool MissesCorrespondingMemberAnnotation(Declaration declaration,
8888
}
8989

9090
var attributeBaseName = AttributeBaseName(declaration, attribute);
91-
92-
//VB_Ext_Key attributes are special in that identity also depends on the first value, the key.
91+
// VB_Ext_Key attributes are special in that identity also depends on the first value, the key.
9392
if (attributeBaseName == "VB_Ext_Key")
9493
{
95-
return !declaration.Annotations.OfType<IAttributeAnnotation>()
96-
.Any(annotation => annotation.Attribute.Equals("VB_Ext_Key") && attribute.Values[0].Equals(annotation.AttributeValues[0]));
94+
return !declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation)
95+
.Any(annotation => annotation.Attribute().Equals("VB_Ext_Key") && attribute.Values[0].Equals(annotation.AttributeValues()[0]));
9796
}
9897

99-
return !declaration.Annotations.OfType<IAttributeAnnotation>()
100-
.Any(annotation => annotation.Attribute.Equals(attributeBaseName));
98+
return !declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation)
99+
.Any(annotation => annotation.Attribute().Equals(attributeBaseName));
101100
}
102101

103102
private static string AttributeBaseName(Declaration declaration, AttributeNode attribute)

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -93,16 +93,15 @@ private static bool MissesCorrespondingModuleAnnotation(Declaration declaration,
9393
{
9494
return false;
9595
}
96-
9796
//VB_Ext_Key attributes are special in that identity also depends on the first value, the key.
9897
if (attribute.Name == "VB_Ext_Key")
9998
{
100-
return !declaration.Annotations.OfType<IAttributeAnnotation>()
101-
.Any(annotation => annotation.Attribute.Equals("VB_Ext_Key") && attribute.Values[0].Equals(annotation.AttributeValues[0]));
99+
return !declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation)
100+
.Any(annotation => annotation.Attribute().Equals("VB_Ext_Key") && attribute.Values[0].Equals(annotation.AttributeValues()[0]));
102101
}
103102

104-
return !declaration.Annotations.OfType<IAttributeAnnotation>()
105-
.Any(annotation => annotation.Attribute.Equals(attribute.Name));
103+
return !declaration.Annotations.Where(pta => pta.Annotation is IAttributeAnnotation)
104+
.Any(annotation => annotation.Attribute().Equals(attribute.Name));
106105
}
107106
}
108107
}

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.OfType<FolderAnnotation>().Any())
42+
.Where(w => !w.Annotations.Any(pta => pta.Annotation is FolderAnnotation))
4343
.ToList();
4444

4545
return modulesWithoutFolderAnnotation

Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteMemberUsageInspection.cs

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

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

6565
foreach (var declaration in declarations)
6666
{
67-
var replacementDocumentation = declaration.Annotations.OfType<ObsoleteAnnotation>().First().ReplacementDocumentation;
67+
var replacementDocumentation = declaration.Annotations
68+
.First(pta => pta.Annotation is ObsoleteAnnotation)
69+
.AnnotationArguments.FirstOrDefault() ?? string.Empty;
6870

6971
issues.AddRange(declaration.References.Select(reference =>
7072
new IdentifierReferenceInspectionResult(this,

Rubberduck.CodeAnalysis/Inspections/Extensions/IgnoreRelatedExtensions.cs

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ static class IgnoreRelatedExtensions
1212
public static bool IsIgnoringInspectionResultFor(this IdentifierReference reference, string inspectionName)
1313
{
1414
return reference.ParentScoping.HasModuleIgnoreFor(inspectionName) ||
15-
reference.Annotations.OfType<IgnoreAnnotation>().Any(ignore => ignore.IsIgnored(inspectionName));
15+
reference.Annotations.Any(ignore => ignore.Annotation is IgnoreAnnotation && ignore.AnnotationArguments.Contains(inspectionName));
1616
}
1717

1818
public static bool IsIgnoringInspectionResultFor(this Declaration declaration, string inspectionName)
@@ -29,12 +29,13 @@ public static bool IsIgnoringInspectionResultFor(this QualifiedContext parserCon
2929
{
3030
return parserContext.ModuleName.IsIgnoringInspectionResultFor(parserContext.Context.Start.Line, declarationFinder, inspectionName);
3131
}
32+
3233
private static bool IsIgnoringInspectionResultFor(this QualifiedModuleName module, int line, DeclarationFinder declarationFinder, string inspectionName)
3334
{
34-
var lineScopedAnnotations = declarationFinder.FindAnnotations(module, line).OfType<IgnoreAnnotation>();
35+
var lineScopedAnnotations = declarationFinder.FindAnnotations<IgnoreAnnotation>(module, line);
3536
var moduleDeclaration = declarationFinder.Members(module).First(decl => decl.DeclarationType.HasFlag(DeclarationType.Module));
3637

37-
var isLineIgnored = lineScopedAnnotations.Any(annotation => annotation.IsIgnored(inspectionName));
38+
var isLineIgnored = lineScopedAnnotations.Any(annotation => annotation.AnnotationArguments.Contains(inspectionName));
3839
var isModuleIgnored = moduleDeclaration.HasModuleIgnoreFor(inspectionName);
3940

4041
return isLineIgnored || isModuleIgnored;
@@ -43,15 +44,15 @@ private static bool IsIgnoringInspectionResultFor(this QualifiedModuleName modul
4344
private static bool HasModuleIgnoreFor(this Declaration declaration, string inspectionName)
4445
{
4546
return Declaration.GetModuleParent(declaration)?.Annotations
46-
.OfType<IgnoreModuleAnnotation>()
47-
.Any(ignoreModule => ignoreModule.IsIgnored(inspectionName)) ?? false;
47+
.Where(pta => pta.Annotation is IgnoreModuleAnnotation)
48+
.Any(ignoreModule => !ignoreModule.AnnotationArguments.Any() || ignoreModule.AnnotationArguments.Contains(inspectionName)) ?? false;
4849
}
4950

5051
private static bool HasIgnoreFor(this Declaration declaration, string inspectionName)
5152
{
5253
return declaration?.Annotations
53-
.OfType<IgnoreAnnotation>()
54-
.Any(ignore => ignore.IsIgnored(inspectionName)) ?? false;
54+
.Where(pta => pta.Annotation is IgnoreAnnotation)
55+
.Any(ignore => ignore.AnnotationArguments.Contains(inspectionName)) ?? false;
5556
}
5657
}
5758
}

0 commit comments

Comments
 (0)