Skip to content

Commit

Permalink
Add analyzer for hostApp in inspections xml-doc
Browse files Browse the repository at this point in the history
  • Loading branch information
MDoerner committed Mar 8, 2020
1 parent 5d3b03b commit 98ea837
Show file tree
Hide file tree
Showing 5 changed files with 405 additions and 42 deletions.
Expand Up @@ -23,7 +23,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete.Excel
/// which cannot be altered by the user without accessing the VBE and altering the VBA project.
/// </why>
/// <reference name="Excel" />
/// <hostapp name="EXCEL.EXE" />
/// <hostApp name="EXCEL.EXE" />
/// <remarks>
/// For performance reasons, the inspection only evaluates hard-coded string literals; string-valued expressions evaluating into a sheet name are ignored.
/// </remarks>
Expand Down
116 changes: 77 additions & 39 deletions RubberduckCodeAnalysis/InspectionXmlDocAnalyzer.cs
Expand Up @@ -54,6 +54,28 @@ public class InspectionXmlDocAnalyzer : DiagnosticAnalyzer
new LocalizableResourceString(nameof(Resources.MissingRequiredLibAttributeDescription), Resources.ResourceManager, typeof(Resources))
);

public const string MissingHostAppElement = "MissingHostAppElement";
private static readonly DiagnosticDescriptor MissingHostAppElementRule = new DiagnosticDescriptor(
MissingHostAppElement,
new LocalizableResourceString(nameof(Resources.MissingInspectionHostAppElement), Resources.ResourceManager, typeof(Resources)),
new LocalizableResourceString(nameof(Resources.MissingInspectionHostAppElementMessageFormat), Resources.ResourceManager, typeof(Resources)),
new LocalizableResourceString(nameof(Resources.XmlDocAnalyzerCategory), Resources.ResourceManager, typeof(Resources)).ToString(),
DiagnosticSeverity.Error,
true,
new LocalizableResourceString(nameof(Resources.MissingInspectionHostAppElementDescription), Resources.ResourceManager, typeof(Resources))
);

public const string MissingRequiredHostAttribute = "MissingRequiredHostAttribute";
private static readonly DiagnosticDescriptor MissingRequiredHostAttributeRule = new DiagnosticDescriptor(
MissingRequiredHostAttribute,
new LocalizableResourceString(nameof(Resources.MissingRequiredHostAttribute), Resources.ResourceManager, typeof(Resources)),
new LocalizableResourceString(nameof(Resources.MissingRequiredHostAttributeMessageFormat), Resources.ResourceManager, typeof(Resources)),
new LocalizableResourceString(nameof(Resources.XmlDocAnalyzerCategory), Resources.ResourceManager, typeof(Resources)).ToString(),
DiagnosticSeverity.Error,
true,
new LocalizableResourceString(nameof(Resources.MissingRequiredHostAttributeDescription), Resources.ResourceManager, typeof(Resources))
);

public const string MissingExampleElement = "MissingExampleElement";
private static readonly DiagnosticDescriptor MissingExampleElementRule = new DiagnosticDescriptor(
MissingExampleElement,
Expand Down Expand Up @@ -142,7 +164,9 @@ public class InspectionXmlDocAnalyzer : DiagnosticAnalyzer
MissingExampleElementRule,
MissingTypeAttributeRule,
InvalidTypeAttributeRule,
DuplicateNameAttributeRule
DuplicateNameAttributeRule,
MissingHostAppElementRule,
MissingRequiredHostAttributeRule
);

public override void Initialize(AnalysisContext context)
Expand All @@ -164,9 +188,19 @@ private static void AnalyzeSymbol(SymbolAnalysisContext context)
CheckWhyElement(context, namedTypeSymbol, xml);
CheckExampleElement(context, namedTypeSymbol, xml);

var requiredLibraryAttributes = namedTypeSymbol.GetAttributes().Where(a => a.AttributeClass.Name == "RequiredLibraryAttribute").ToList();
CheckReferenceElement(context, namedTypeSymbol, xml, requiredLibraryAttributes);
CheckRequiredLibAttribute(context, namedTypeSymbol, xml, requiredLibraryAttributes);
var attributes = namedTypeSymbol.GetAttributes();
var requiredLibraryAttributes = attributes
.Where(a => a.AttributeClass.Name == "RequiredLibraryAttribute")
.ToList();
var requiredHostAttributes = attributes
.Where(a => a.AttributeClass.Name == "RequiredHostAttribute")
.ToList();

CheckAttributeRelatedElementElements(context, namedTypeSymbol, xml, requiredLibraryAttributes, "reference", MissingReferenceElementRule);
CheckAttributeRelatedElementElements(context, namedTypeSymbol, xml, requiredHostAttributes, "hostApp", MissingHostAppElementRule);

CheckXmlRelatedAttribute(context, namedTypeSymbol, xml, requiredLibraryAttributes, "reference", MissingRequiredLibAttributeRule);
CheckXmlRelatedAttribute(context, namedTypeSymbol, xml, requiredHostAttributes, "hostApp", MissingRequiredHostAttributeRule);
}

private static bool IsInspectionClass(INamedTypeSymbol namedTypeSymbol)
Expand Down Expand Up @@ -206,54 +240,66 @@ private static string CheckNameAttributeAndReturnValue(SymbolAnalysisContext con
return nameAttribute?.Value;
}

private static void CheckReferenceElement(SymbolAnalysisContext context, INamedTypeSymbol symbol, XElement xml, ICollection<AttributeData> requiredLibAttributes)
private static void CheckAttributeRelatedElementElements(SymbolAnalysisContext context, INamedTypeSymbol symbol, XElement xml, ICollection<AttributeData> requiredAttributes, string xmlElementName, DiagnosticDescriptor requiredElementDescriptor)
{
if (requiredLibAttributes.Any() && !xml.Elements("reference").Any())
if (requiredAttributes.Any() && !xml.Elements(xmlElementName).Any())
{
var diagnostic = Diagnostic.Create(MissingReferenceElementRule, symbol.Locations[0], symbol.Name);
var diagnostic = Diagnostic.Create(requiredElementDescriptor, symbol.Locations[0], symbol.Name);
context.ReportDiagnostic(diagnostic);
}

var xmlRefLibs = new List<string>();
foreach (var element in xml.Elements("reference"))
var xmlElementNames = new List<string>();
foreach (var element in xml.Elements(xmlElementName))
{
var name = CheckNameAttributeAndReturnValue(context, element, symbol.Locations[0]);
if (name != null)
{
xmlRefLibs.Add(name);
xmlElementNames.Add(name);
}
}

var duplicateNames = xmlRefLibs
.GroupBy(name => name)
.Where(group => group.Count() > 1)
.Select(group => group.Key);
foreach (var name in duplicateNames)
{
var diagnostic = Diagnostic.Create(DuplicateNameAttributeRule, symbol.Locations[0], name, "reference");
context.ReportDiagnostic(diagnostic);
}

foreach (var attribute in requiredLibAttributes)
CheckForDuplicateNames(context, symbol, xmlElementName, xmlElementNames);

var requiredNames = requiredAttributes
.Where(a => a.ConstructorArguments.Length > 0)
.Select(a => a.ConstructorArguments[0].Value.ToString())
.ToList();
foreach (var requiredName in requiredNames)
{
var requiredLib = attribute.ConstructorArguments[0].Value.ToString();
if (xmlRefLibs.All(lib => lib != requiredLib))
if (requiredNames.All(lib => lib != requiredName))
{
var diagnostic = Diagnostic.Create(MissingReferenceElementRule, symbol.Locations[0], symbol.Name);
var diagnostic = Diagnostic.Create(requiredElementDescriptor, symbol.Locations[0], symbol.Name);
context.ReportDiagnostic(diagnostic);
}
}
}

private static void CheckRequiredLibAttribute(SymbolAnalysisContext context, INamedTypeSymbol symbol, XElement xml, IEnumerable<AttributeData> requiredLibAttributes)
private static void CheckForDuplicateNames(SymbolAnalysisContext context, INamedTypeSymbol symbol, string xmlElementName, List<string> names)
{
var duplicateNames = names
.GroupBy(name => name)
.Where(group => @group.Count() > 1)
.Select(group => @group.Key);
foreach (var name in duplicateNames)
{
var diagnostic = Diagnostic.Create(DuplicateNameAttributeRule, symbol.Locations[0], name, xmlElementName);
context.ReportDiagnostic(diagnostic);
}
}

private static void CheckXmlRelatedAttribute(SymbolAnalysisContext context, INamedTypeSymbol symbol, XElement xml, IEnumerable<AttributeData> requiredAttributes, string xmlElementName, DiagnosticDescriptor requiredAttributeDescriptor)
{
var requiredLibs = requiredLibAttributes.Select(a => a.ConstructorArguments[0].Value.ToString()).ToList();
foreach (var element in xml.Elements("reference"))
var requiredNames = requiredAttributes
.Where(a => a.ConstructorArguments.Length > 0)
.Select(a => a.ConstructorArguments[0].Value.ToString())
.ToList();

foreach (var element in xml.Elements(xmlElementName))
{
var xmlRefLib = element.Attribute("name")?.Value;
if (xmlRefLib == null || requiredLibs.All(lib => lib != xmlRefLib))
var name = element.Attribute("name")?.Value;
if (name == null || requiredNames.All(lib => lib != name))
{
var diagnostic = Diagnostic.Create(MissingRequiredLibAttributeRule, symbol.Locations[0], symbol.Name, xmlRefLib);
var diagnostic = Diagnostic.Create(requiredAttributeDescriptor, symbol.Locations[0], symbol.Name, name);
context.ReportDiagnostic(diagnostic);
}
}
Expand Down Expand Up @@ -296,15 +342,7 @@ private static void CheckModuleElements(SymbolAnalysisContext context, INamedTyp
CheckTypeAttribute(context, module, symbol.Locations[0]);
}

var duplicateNames = moduleNames
.GroupBy(name => name)
.Where(group => group.Count() > 1)
.Select(group => group.Key);
foreach (var name in duplicateNames)
{
var diagnostic = Diagnostic.Create(DuplicateNameAttributeRule, symbol.Locations[0], name, "module");
context.ReportDiagnostic(diagnostic);
}
CheckForDuplicateNames(context, symbol, "module", moduleNames);
}

private static void CheckHasResultAttribute(SymbolAnalysisContext context, XElement element, Location location)
Expand Down
54 changes: 54 additions & 0 deletions RubberduckCodeAnalysis/Resources.Designer.cs

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

18 changes: 18 additions & 0 deletions RubberduckCodeAnalysis/Resources.resx
Expand Up @@ -294,4 +294,22 @@
<data name="DuplicateNameAttributeMessageFormat" xml:space="preserve">
<value>The value '{0}' is used in the 'name' attribute of multiple '{1}' elements.</value>
</data>
<data name="MissingRequiredHostAttribute" xml:space="preserve">
<value>Missing 'RequiredHost' attribute</value>
</data>
<data name="MissingRequiredHostAttributeDescription" xml:space="preserve">
<value>The &lt;hostApp name="RequiredHost" /&gt; element means to document the presence of a [RequiredHostAttribute]. If the attribute is correctly missing, the xml-doc element should be removed.</value>
</data>
<data name="MissingRequiredHostAttributeMessageFormat" xml:space="preserve">
<value>XML documentation of type '{0}' includes a &lt;hostApp&gt; element, but no corresponding [RequiredHostAttribute] is decorating the inspection type. Expected: [RequiredHost("{1}")].</value>
</data>
<data name="MissingInspectionHostAppElement" xml:space="preserve">
<value>Missing xml-doc 'hostApp' element</value>
</data>
<data name="MissingInspectionHostAppElementDescription" xml:space="preserve">
<value>XML documentation for inspections with a [RequiredHostAttribute] must include a &lt;hostApp&gt; element with a 'name' attribute with the same value as the [RequiredHostAttribute]. For example [RequiredHost("Excel")] mandates &lt;hostApp name="Excel" /&gt;.</value>
</data>
<data name="MissingInspectionHostAppElementMessageFormat" xml:space="preserve">
<value>XML documentation for type '{0}' is missing a 'hostApp' element.</value>
</data>
</root>

0 comments on commit 98ea837

Please sign in to comment.