Skip to content

Commit 1c8f7a4

Browse files
committed
Add SuperfluousAnnotationArgumentsInspection
Also add allowed number of arguments to IAnnotation interface.
1 parent d21dacf commit 1c8f7a4

23 files changed

+287
-18
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAnnotationArgumentInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -14,10 +14,10 @@
1414
namespace Rubberduck.Inspections.Concrete
1515
{
1616
/// <summary>
17-
/// Warns about a malformed Rubberduck annotation that is missing an argument.
17+
/// Warns about a malformed Rubberduck annotation that is missing one or more arguments.
1818
/// </summary>
1919
/// <why>
20-
/// Some annotations require arguments; if the argument isn't specified, the annotation is nothing more than an obscure comment.
20+
/// Some annotations require arguments; if the required number of arguments isn't specified, the annotation is nothing more than an obscure comment.
2121
/// </why>
2222
/// <example hasResults="true">
2323
/// <![CDATA[
Lines changed: 93 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,93 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using Rubberduck.Inspections.Abstract;
5+
using Rubberduck.Inspections.Results;
6+
using Rubberduck.Parsing;
7+
using Rubberduck.Parsing.Annotations;
8+
using Rubberduck.Parsing.Inspections.Abstract;
9+
using Rubberduck.Parsing.Symbols;
10+
using Rubberduck.Resources.Inspections;
11+
using Rubberduck.Parsing.VBA;
12+
using Rubberduck.Parsing.VBA.DeclarationCaching;
13+
using Rubberduck.VBEditor;
14+
15+
namespace Rubberduck.Inspections.Concrete
16+
{
17+
/// <summary>
18+
/// Warns about Rubberduck annotations with more arguments than allowed.
19+
/// </summary>
20+
/// <why>
21+
/// Most annotations only process a limited number of arguments; superfluous arguments are ignored.
22+
/// </why>
23+
/// <example hasResults="true">
24+
/// <![CDATA[
25+
/// '@Folder "MyFolder.MySubFolder" "SomethingElse
26+
/// '@PredeclaredId True
27+
/// Option Explicit
28+
/// ' ...
29+
/// ]]>
30+
/// </example>
31+
/// <example hasResults="false">
32+
/// <![CDATA[
33+
/// '@Folder("MyFolder.MySubFolder")
34+
/// '@PredeclaredId
35+
/// Option Explicit
36+
/// ' ...
37+
/// ]]>
38+
/// </example>
39+
public sealed class SuperfluousAnnotationArgumentInspection : InspectionBase
40+
{
41+
public SuperfluousAnnotationArgumentInspection(IDeclarationFinderProvider declarationFinderProvider)
42+
: base(declarationFinderProvider)
43+
{}
44+
45+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
46+
{
47+
var finder = DeclarationFinderProvider.DeclarationFinder;
48+
49+
return finder.UserDeclarations(DeclarationType.Module)
50+
.Where(module => module != null)
51+
.SelectMany(module => DoGetInspectionResults(module.QualifiedModuleName, finder))
52+
.ToList();
53+
}
54+
55+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module)
56+
{
57+
var finder = DeclarationFinderProvider.DeclarationFinder;
58+
return DoGetInspectionResults(module, finder);
59+
}
60+
61+
private IEnumerable<IInspectionResult> DoGetInspectionResults(QualifiedModuleName module, DeclarationFinder finder)
62+
{
63+
var objectionableAnnotations = finder.FindAnnotations(module)
64+
.Where(IsResultAnnotation);
65+
66+
return objectionableAnnotations
67+
.Select(InspectionResult)
68+
.ToList();
69+
}
70+
71+
private static bool IsResultAnnotation(IParseTreeAnnotation pta)
72+
{
73+
var allowedArguments = pta.Annotation.AllowedArguments;
74+
return allowedArguments.HasValue && allowedArguments.Value < pta.AnnotationArguments.Count;
75+
}
76+
77+
private IInspectionResult InspectionResult(IParseTreeAnnotation pta)
78+
{
79+
var qualifiedContext = new QualifiedContext(pta.QualifiedSelection.QualifiedName, pta.Context);
80+
return new QualifiedContextInspectionResult(
81+
this,
82+
ResultDescription(pta),
83+
qualifiedContext);
84+
}
85+
86+
private static string ResultDescription(IParseTreeAnnotation pta)
87+
{
88+
return string.Format(
89+
InspectionResults.SuperfluousAnnotationArgumentInspection,
90+
pta.Annotation.Name);
91+
}
92+
}
93+
}

Rubberduck.Parsing/Annotations/AnnotationBase.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,15 +7,17 @@ public abstract class AnnotationBase : IAnnotation
77
{
88
public bool AllowMultiple { get; }
99
public int RequiredArguments { get; }
10+
public int? AllowedArguments { get; }
1011
public string Name { get; }
1112
public AnnotationTarget Target { get; }
1213

13-
protected AnnotationBase(string name, AnnotationTarget target, int requiredArguments = 0, bool allowMultiple = false)
14+
protected AnnotationBase(string name, AnnotationTarget target, int requiredArguments = 0, int? allowedArguments = 0, bool allowMultiple = false)
1415
{
1516
Name = name;
1617
Target = target;
1718
AllowMultiple = allowMultiple;
1819
RequiredArguments = requiredArguments;
20+
AllowedArguments = allowedArguments;
1921
}
2022

2123
public virtual IReadOnlyList<string> ProcessAnnotationArguments(IEnumerable<string> arguments)

Rubberduck.Parsing/Annotations/Concrete/FlexibleAttributeAnnotationBase.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ namespace Rubberduck.Parsing.Annotations
77
public abstract class FlexibleAttributeAnnotationBase : AnnotationBase, IAttributeAnnotation
88
{
99
protected FlexibleAttributeAnnotationBase(string name, AnnotationTarget target, bool allowMultiple = false)
10-
: base(name, target, 2, allowMultiple) //We need at least the attribute name and one value for it.
10+
: base(name, target, 2, null, allowMultiple) //We need at least the attribute name and one value for it.
1111
{}
1212

1313
public IReadOnlyList<string> AnnotationToAttributeValues(IReadOnlyList<string> annotationValues)

Rubberduck.Parsing/Annotations/Concrete/FlexibleAttributeValueAnnotationBase.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
1-
using System;
2-
using System.Collections.Generic;
1+
using System.Collections.Generic;
32
using System.Linq;
43
using Rubberduck.Common;
54

@@ -11,7 +10,7 @@ public abstract class FlexibleAttributeValueAnnotationBase : AnnotationBase, IAt
1110
private readonly int _numberOfValues;
1211

1312
protected FlexibleAttributeValueAnnotationBase(string name, AnnotationTarget target, string attribute, int numberOfValues)
14-
: base(name, target, numberOfValues)
13+
: base(name, target, numberOfValues, numberOfValues)
1514
{
1615
_attribute = attribute;
1716
_numberOfValues = numberOfValues;

Rubberduck.Parsing/Annotations/Concrete/FolderAnnotation.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@
66
public sealed class FolderAnnotation : AnnotationBase
77
{
88
public FolderAnnotation()
9-
: base("Folder", AnnotationTarget.Module, 1)
9+
: base("Folder", AnnotationTarget.Module, 1, 1)
1010
{}
1111
}
1212
}

Rubberduck.Parsing/Annotations/Concrete/IgnoreAnnotation.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@
66
public sealed class IgnoreAnnotation : AnnotationBase
77
{
88
public IgnoreAnnotation()
9-
: base("Ignore", AnnotationTarget.General, 1, true)
9+
: base("Ignore", AnnotationTarget.General, 1, null, true)
1010
{}
1111
}
1212
}

Rubberduck.Parsing/Annotations/Concrete/IgnoreModuleAnnotation.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@
66
public sealed class IgnoreModuleAnnotation : AnnotationBase
77
{
88
public IgnoreModuleAnnotation()
9-
: base("IgnoreModule", AnnotationTarget.Module, 1, true)
9+
: base("IgnoreModule", AnnotationTarget.Module, allowedArguments: null, allowMultiple: true)
1010
{}
1111
}
1212
}

Rubberduck.Parsing/Annotations/Concrete/IgnoreTestAnnotation.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@
66
public sealed class IgnoreTestAnnotation : AnnotationBase
77
{
88
public IgnoreTestAnnotation()
9-
: base("IgnoreTest", AnnotationTarget.Member)
10-
{ }
9+
: base("IgnoreTest", AnnotationTarget.Member, allowedArguments: 1)
10+
{}
1111
}
1212
}

Rubberduck.Parsing/Annotations/Concrete/ObsoleteAnnotation.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ public sealed class ObsoleteAnnotation : AnnotationBase
1212
public string ReplacementDocumentation { get; private set; }
1313

1414
public ObsoleteAnnotation()
15-
: base("Obsolete", AnnotationTarget.Member | AnnotationTarget.Variable)
15+
: base("Obsolete", AnnotationTarget.Member | AnnotationTarget.Variable, allowedArguments: 1)
1616
{}
1717

1818
public override IReadOnlyList<string> ProcessAnnotationArguments(IEnumerable<string> arguments)

0 commit comments

Comments
 (0)