Skip to content

Commit

Permalink
adding @IgnoreModule annotation; closes #2352
Browse files Browse the repository at this point in the history
  • Loading branch information
retailcoder committed Feb 28, 2017
1 parent 8186131 commit 5d75299
Show file tree
Hide file tree
Showing 7 changed files with 145 additions and 19 deletions.
19 changes: 9 additions & 10 deletions RetailCoder.VBE/Inspections/Abstract/InspectionBase.cs
Expand Up @@ -116,28 +116,27 @@ protected bool IsIgnoringInspectionResultFor(IVBComponent component, int line)

protected bool IsIgnoringInspectionResultFor(Declaration declaration, string inspectionName)
{
var isIgnoredAtModuleLevel =
Declaration.GetModuleParent(declaration).Annotations
.Any(annotation => annotation.AnnotationType == AnnotationType.IgnoreModule
&& ((IgnoreModuleAnnotation) annotation).IsIgnored(inspectionName));


if (declaration.DeclarationType == DeclarationType.Parameter)
{
return declaration.ParentDeclaration.Annotations.Any(annotation =>
return isIgnoredAtModuleLevel || declaration.ParentDeclaration.Annotations.Any(annotation =>
annotation.AnnotationType == AnnotationType.Ignore
&& ((IgnoreAnnotation)annotation).IsIgnored(inspectionName));
}

return declaration.Annotations.Any(annotation =>
return isIgnoredAtModuleLevel || declaration.Annotations.Any(annotation =>
annotation.AnnotationType == AnnotationType.Ignore
&& ((IgnoreAnnotation)annotation).IsIgnored(inspectionName));
}

protected bool IsIgnoringInspectionResultFor(IdentifierReference reference, string inspectionName)
{
if (reference == null)
{
return false;
}

return reference.Annotations.Any(annotation =>
annotation.AnnotationType == AnnotationType.Ignore
&& ((IgnoreAnnotation)annotation).IsIgnored(inspectionName));
return reference != null && reference.IsIgnoringInspectionResultFor(inspectionName);
}

public int CompareTo(IInspection other)
Expand Down
1 change: 1 addition & 0 deletions Rubberduck.Parsing/Annotations/AnnotationType.cs
Expand Up @@ -10,6 +10,7 @@ public enum AnnotationType
TestCleanup,
IgnoreTest,
Ignore,
IgnoreModule,
Folder,
NoIndent,
Interface
Expand Down
35 changes: 35 additions & 0 deletions Rubberduck.Parsing/Annotations/IgnoreModuleAnnotation.cs
@@ -0,0 +1,35 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.VBEditor;

namespace Rubberduck.Parsing.Annotations
{
public sealed class IgnoreModuleAnnotation : AnnotationBase
{
private readonly IEnumerable<string> _inspectionNames;

public IgnoreModuleAnnotation(QualifiedSelection qualifiedSelection, IEnumerable<string> parameters)
: base(AnnotationType.IgnoreModule, qualifiedSelection)
{
_inspectionNames = parameters;
}

public IEnumerable<string> InspectionNames
{
get
{
return _inspectionNames;
}
}

public bool IsIgnored(string inspectionName)
{
return !_inspectionNames.Any() || _inspectionNames.Contains(inspectionName);
}

public override string ToString()
{
return string.Format("Ignored inspections: {0}", string.Join(", ", _inspectionNames));
}
}
}
13 changes: 7 additions & 6 deletions Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs
Expand Up @@ -19,6 +19,7 @@ public VBAParserAnnotationFactory()
_creators.Add(AnnotationType.TestInitialize.ToString().ToUpperInvariant(), typeof(TestInitializeAnnotation));
_creators.Add(AnnotationType.TestCleanup.ToString().ToUpperInvariant(), typeof(TestCleanupAnnotation));
_creators.Add(AnnotationType.Ignore.ToString().ToUpperInvariant(), typeof(IgnoreAnnotation));
_creators.Add(AnnotationType.IgnoreModule.ToString().ToUpperInvariant(), typeof(IgnoreModuleAnnotation));
_creators.Add(AnnotationType.IgnoreTest.ToString().ToUpperInvariant(), typeof(IgnoreTestAnnotation));
_creators.Add(AnnotationType.Folder.ToString().ToUpperInvariant(), typeof(FolderAnnotation));
_creators.Add(AnnotationType.NoIndent.ToString().ToUpperInvariant(), typeof(NoIndentAnnotation));
Expand All @@ -27,14 +28,14 @@ public VBAParserAnnotationFactory()

public IAnnotation Create(VBAParser.AnnotationContext context, QualifiedSelection qualifiedSelection)
{
string annotationName = context.annotationName().GetText();
List<string> parameters = AnnotationParametersFromContext(context);
var annotationName = context.annotationName().GetText();
var parameters = AnnotationParametersFromContext(context);
return CreateAnnotation(annotationName, parameters, qualifiedSelection);
}

private static List<string> AnnotationParametersFromContext(VBAParser.AnnotationContext context)
{
List<string> parameters = new List<string>();
var parameters = new List<string>();
var argList = context.annotationArgList();
if (argList != null)
{
Expand All @@ -45,10 +46,10 @@ private static List<string> AnnotationParametersFromContext(VBAParser.Annotation

private IAnnotation CreateAnnotation(string annotationName, List<string> parameters, QualifiedSelection qualifiedSelection)
{
Type annotationCLRType = null;
if (_creators.TryGetValue(annotationName.ToUpperInvariant(), out annotationCLRType))
Type annotationClrType;
if (_creators.TryGetValue(annotationName.ToUpperInvariant(), out annotationClrType))
{
return (IAnnotation)Activator.CreateInstance(annotationCLRType, qualifiedSelection, parameters);
return (IAnnotation)Activator.CreateInstance(annotationClrType, qualifiedSelection, parameters);
}
return null;
}
Expand Down
1 change: 1 addition & 0 deletions Rubberduck.Parsing/Rubberduck.Parsing.csproj
Expand Up @@ -66,6 +66,7 @@
<Compile Include="Annotations\IAnnotation.cs" />
<Compile Include="Annotations\IAnnotationFactory.cs" />
<Compile Include="Annotations\IgnoreAnnotation.cs" />
<Compile Include="Annotations\IgnoreModuleAnnotation.cs" />
<Compile Include="Annotations\InterfaceAnnotation.cs" />
<Compile Include="Annotations\InvalidAnnotationArgumentException.cs" />
<Compile Include="Annotations\ModuleCleanupAnnotation.cs" />
Expand Down
11 changes: 8 additions & 3 deletions Rubberduck.Parsing/Symbols/IdentifierReference.cs
Expand Up @@ -73,9 +73,14 @@ public class IdentifierReference : IEquatable<IdentifierReference>

public bool IsIgnoringInspectionResultFor(string inspectionName)
{
return Annotations.Any(annotation =>
annotation.AnnotationType == AnnotationType.Ignore
&& ((IgnoreAnnotation)annotation).IsIgnored(inspectionName));
var isIgnoredAtModuleLevel =
Declaration.GetModuleParent(_parentScopingDeclaration).Annotations
.Any(annotation => annotation.AnnotationType == AnnotationType.IgnoreModule
&& ((IgnoreModuleAnnotation)annotation).IsIgnored(inspectionName));

return isIgnoredAtModuleLevel || Annotations.Any(annotation =>
annotation.AnnotationType == AnnotationType.Ignore
&& ((IgnoreAnnotation) annotation).IsIgnored(inspectionName));
}

private readonly bool _hasExplicitLetStatement;
Expand Down
84 changes: 84 additions & 0 deletions RubberduckTests/Inspections/ConstantNotUsedInspectionTests.cs
Expand Up @@ -131,6 +131,90 @@ End Sub
Assert.AreEqual(0, inspectionResults.Count());
}

[TestMethod]
[TestCategory("Inspections")]
public void ConstantNotUsed_IgnoreModule_All_YieldsNoResult()
{
const string inputCode =
@"'@IgnoreModule
Public Sub Foo()
Const const1 As Integer = 9
End Sub";

//Arrange
var builder = new MockVbeBuilder();
IVBComponent component;
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
var mockHost = new Mock<IHostApplication>();
mockHost.SetupAllProperties();
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));

parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

var inspection = new ConstantNotUsedInspection(parser.State);
var inspectionResults = inspection.GetInspectionResults();

Assert.IsFalse(inspectionResults.Any());
}

[TestMethod]
[TestCategory("Inspections")]
public void ConstantNotUsed_IgnoreModule_AnnotationName_YieldsNoResult()
{
const string inputCode =
@"'@IgnoreModule ConstantNotUsed
Public Sub Foo()
Const const1 As Integer = 9
End Sub";

//Arrange
var builder = new MockVbeBuilder();
IVBComponent component;
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
var mockHost = new Mock<IHostApplication>();
mockHost.SetupAllProperties();
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));

parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

var inspection = new ConstantNotUsedInspection(parser.State);
var inspectionResults = inspection.GetInspectionResults();

Assert.IsFalse(inspectionResults.Any());
}

[TestMethod]
[TestCategory("Inspections")]
public void ConstantNotUsed_IgnoreModule_OtherAnnotationName_YieldsResults()
{
const string inputCode =
@"'@IgnoreModule VariableNotUsed
Public Sub Foo()
Const const1 As Integer = 9
End Sub";

//Arrange
var builder = new MockVbeBuilder();
IVBComponent component;
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
var mockHost = new Mock<IHostApplication>();
mockHost.SetupAllProperties();
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));

parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

var inspection = new ConstantNotUsedInspection(parser.State);
var inspectionResults = inspection.GetInspectionResults();

Assert.IsTrue(inspectionResults.Any());
}

[TestMethod]
[TestCategory("Inspections")]
public void ConstantNotUsed_Ignored_DoesNotReturnResult()
Expand Down

0 comments on commit 5d75299

Please sign in to comment.