Skip to content

Commit

Permalink
Merge branch 'next' into next
Browse files Browse the repository at this point in the history
  • Loading branch information
retailcoder committed Mar 19, 2017
2 parents e88704b + 5a43c25 commit 2fc8fc9
Show file tree
Hide file tree
Showing 2 changed files with 31 additions and 3 deletions.
Expand Up @@ -14,18 +14,19 @@ namespace Rubberduck.Inspections
public sealed class ObsoleteCommentSyntaxInspection : InspectionBase, IParseTreeInspection
{
private IEnumerable<QualifiedContext> _parseTreeResults;
public IEnumerable<QualifiedContext<VBAParser.RemCommentContext>> ParseTreeResults { get { return _parseTreeResults.OfType<QualifiedContext<VBAParser.RemCommentContext>>(); } }

public ObsoleteCommentSyntaxInspection(RubberduckParserState state) : base(state, CodeInspectionSeverity.Suggestion) { }

public override CodeInspectionType InspectionType { get { return CodeInspectionType.LanguageOpportunities; } }

public override IEnumerable<IInspectionResult> GetInspectionResults()
{
if (_parseTreeResults == null)
if (ParseTreeResults == null)
{
return Enumerable.Empty<IInspectionResult>();
}
return _parseTreeResults.Where(context => !IsIgnoringInspectionResultFor(context.ModuleName.Component, context.Context.Start.Line))
return ParseTreeResults.Where(context => !IsIgnoringInspectionResultFor(context.ModuleName.Component, context.Context.Start.Line))
.Select(context => new ObsoleteCommentSyntaxInspectionResult(this, new QualifiedContext<ParserRuleContext>(context.ModuleName, context.Context)));
}

Expand Down
Expand Up @@ -5,6 +5,7 @@
using Rubberduck.Inspections;
using Rubberduck.Inspections.Concrete.Rubberduck.Inspections;
using Rubberduck.Inspections.QuickFixes;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.Inspections.Resources;
using Rubberduck.Settings;
Expand Down Expand Up @@ -39,7 +40,7 @@ public void ObsoleteCommentSyntax_ReturnsResult()

[TestMethod]
[TestCategory("Inspections")]
public void ObsoleteCommentSyntax_DoesNotReturnResult()
public void ObsoleteCommentSyntax_DoesNotReturnResult_QuoteComment()
{
const string inputCode = @"' test";

Expand All @@ -58,6 +59,32 @@ public void ObsoleteCommentSyntax_DoesNotReturnResult()
Assert.AreEqual(0, inspectionResults.Count());
}

[TestMethod]
[TestCategory("Inspections")]
public void ObsoleteCommentSyntax_DoesNotReturnResult_OtherParseInspectionFires()
{
const string inputCode = @"
Sub foo()
Dim i As String
i = """"
End Sub";

var settings = new Mock<IGeneralConfigService>();
var config = GetTestConfig();
settings.Setup(x => x.LoadConfiguration()).Returns(config);

IVBComponent component;
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out component);
var state = MockParser.CreateAndParse(vbe.Object);

var inspection = new ObsoleteCommentSyntaxInspection(state);
var emptyStringLiteralInspection = new EmptyStringLiteralInspection(state);
var inspector = new Inspector(settings.Object, new IInspection[] { inspection, emptyStringLiteralInspection });

var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
Assert.AreEqual(0, inspectionResults.Count(r => r is ObsoleteCommentSyntaxInspectionResult));
}

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

0 comments on commit 2fc8fc9

Please sign in to comment.