Skip to content

Commit 400ff2f

Browse files
committed
Remove no longer required part of IllegalAnnotationInspection
1 parent 8c5f900 commit 400ff2f

File tree

2 files changed

+2
-68
lines changed

2 files changed

+2
-68
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs

Lines changed: 1 addition & 67 deletions
Original file line numberDiff line numberDiff line change
@@ -20,18 +20,11 @@ public IllegalAnnotationInspection(RubberduckParserState state)
2020

2121
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2222
{
23-
var illegalAnnotations = new List<IAnnotation>();
24-
2523
var userDeclarations = State.DeclarationFinder.AllUserDeclarations.ToList();
2624
var identifierReferences = State.DeclarationFinder.AllIdentifierReferences().ToList();
2725
var annotations = State.AllAnnotations;
2826

29-
illegalAnnotations.AddRange(UnboundAnnotations(annotations, userDeclarations, identifierReferences));
30-
illegalAnnotations.AddRange(NonIdentifierAnnotationsOnIdentifiers(identifierReferences));
31-
illegalAnnotations.AddRange(NonModuleAnnotationsOnModules(userDeclarations));
32-
illegalAnnotations.AddRange(NonMemberAnnotationsOnMembers(userDeclarations));
33-
illegalAnnotations.AddRange(NonVariableAnnotationsOnVariables(userDeclarations));
34-
illegalAnnotations.AddRange(NonGeneralAnnotationsWhereOnlyGeneralAnnotationsBelong(userDeclarations));
27+
var illegalAnnotations = UnboundAnnotations(annotations, userDeclarations, identifierReferences);
3528

3629
return illegalAnnotations.Select(annotation =>
3730
new QualifiedContextInspectionResult(
@@ -50,64 +43,5 @@ private static ICollection<IAnnotation> UnboundAnnotations(IEnumerable<IAnnotati
5043

5144
return annotations.Where(annotation => !boundAnnotationsSelections.Contains(annotation.QualifiedSelection)).ToList();
5245
}
53-
54-
private static ICollection<IAnnotation> NonIdentifierAnnotationsOnIdentifiers(IEnumerable<IdentifierReference> identifierReferences)
55-
{
56-
return identifierReferences
57-
.SelectMany(reference => reference.Annotations)
58-
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation))
59-
.ToList();
60-
}
61-
62-
private static ICollection<IAnnotation> NonModuleAnnotationsOnModules(IEnumerable<Declaration> userDeclarations)
63-
{
64-
return userDeclarations
65-
.Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Module))
66-
.SelectMany(moduleDeclaration => moduleDeclaration.Annotations)
67-
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.ModuleAnnotation))
68-
.ToList();
69-
}
70-
71-
private static ICollection<IAnnotation> NonMemberAnnotationsOnMembers(IEnumerable<Declaration> userDeclarations)
72-
{
73-
return userDeclarations
74-
.Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Member))
75-
.SelectMany(member => member.Annotations)
76-
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.MemberAnnotation))
77-
.ToList();
78-
}
79-
80-
private static ICollection<IAnnotation> NonVariableAnnotationsOnVariables(IEnumerable<Declaration> userDeclarations)
81-
{
82-
return userDeclarations
83-
.Where(declaration => VariableAnnotationDeclarationTypes.Contains(declaration.DeclarationType))
84-
.SelectMany(declaration => declaration.Annotations)
85-
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.VariableAnnotation))
86-
.ToList();
87-
}
88-
89-
private static readonly HashSet<DeclarationType> VariableAnnotationDeclarationTypes = new HashSet<DeclarationType>()
90-
{
91-
DeclarationType.Variable,
92-
DeclarationType.Control,
93-
DeclarationType.Constant,
94-
DeclarationType.Enumeration,
95-
DeclarationType.EnumerationMember,
96-
DeclarationType.UserDefinedType,
97-
DeclarationType.UserDefinedType,
98-
DeclarationType.UserDefinedTypeMember
99-
};
100-
101-
private static ICollection<IAnnotation> NonGeneralAnnotationsWhereOnlyGeneralAnnotationsBelong(IEnumerable<Declaration> userDeclarations)
102-
{
103-
return userDeclarations
104-
.Where(declaration => !declaration.DeclarationType.HasFlag(DeclarationType.Module)
105-
&& !declaration.DeclarationType.HasFlag(DeclarationType.Member)
106-
&& !VariableAnnotationDeclarationTypes.Contains(declaration.DeclarationType)
107-
&& declaration.DeclarationType != DeclarationType.Project)
108-
.SelectMany(member => member.Annotations)
109-
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.GeneralAnnotation))
110-
.ToList();
111-
}
11246
}
11347
}

Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -178,7 +178,7 @@ private Declaration CreateDeclaration(
178178
selection,
179179
isArray,
180180
true,
181-
FindVariableAnnotations(selection.StartLine),
181+
FindGeneralAnnotations(selection.StartLine),
182182
attributes);
183183
break;
184184
case DeclarationType.LibraryProcedure:

0 commit comments

Comments
 (0)