Skip to content

Commit 393c10d

Browse files
authored
Merge pull request #2052 from Hosch250/inspectionBugs
Inspection bugs
2 parents 7b0a9b8 + df50e7c commit 393c10d

File tree

62 files changed

+2598
-178
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

62 files changed

+2598
-178
lines changed

RetailCoder.VBE/Inspections/AssignedByValParameterInspectionResult.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,9 +13,10 @@ public class AssignedByValParameterInspectionResult : InspectionResultBase
1313
public AssignedByValParameterInspectionResult(IInspection inspection, Declaration target)
1414
: base(inspection, target)
1515
{
16-
_quickFixes = new[]
16+
_quickFixes = new CodeInspectionQuickFix[]
1717
{
1818
new PassParameterByReferenceQuickFix(target.Context, QualifiedSelection),
19+
new IgnoreOnceQuickFix(Context, QualifiedSelection, inspection.AnnotationName)
1920
};
2021
}
2122

RetailCoder.VBE/Inspections/EmptyStringLiteralInspection.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -26,8 +26,9 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2626
{
2727
return new InspectionResultBase[] { };
2828
}
29-
return ParseTreeResults.EmptyStringLiterals.Select(
30-
context => new EmptyStringLiteralInspectionResult(this,
29+
return ParseTreeResults.EmptyStringLiterals
30+
.Where(s => !IsInspectionDisabled(s.ModuleName.Component, s.Context.Start.Line))
31+
.Select(context => new EmptyStringLiteralInspectionResult(this,
3132
new QualifiedContext<ParserRuleContext>(context.ModuleName, context.Context)));
3233
}
3334

RetailCoder.VBE/Inspections/EmptyStringLiteralInspectionResult.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -13,9 +13,10 @@ public class EmptyStringLiteralInspectionResult : InspectionResultBase
1313
public EmptyStringLiteralInspectionResult(IInspection inspection, QualifiedContext<ParserRuleContext> qualifiedContext)
1414
: base(inspection, qualifiedContext.ModuleName, qualifiedContext.Context)
1515
{
16-
_quickFixes = new[]
16+
_quickFixes = new CodeInspectionQuickFix[]
1717
{
18-
new RepaceEmptyStringLiteralStatementQuickFix(Context, QualifiedSelection),
18+
new RepaceEmptyStringLiteralStatementQuickFix(Context, QualifiedSelection),
19+
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName)
1920
};
2021
}
2122

RetailCoder.VBE/Inspections/EncapsulatePublicFieldInspectionResult.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,9 +16,10 @@ public class EncapsulatePublicFieldInspectionResult : InspectionResultBase
1616
public EncapsulatePublicFieldInspectionResult(IInspection inspection, Declaration target, RubberduckParserState state)
1717
: base(inspection, target)
1818
{
19-
_quickFixes = new[]
19+
_quickFixes = new CodeInspectionQuickFix[]
2020
{
2121
new EncapsulateFieldQuickFix(target.Context, target.QualifiedSelection, target, state),
22+
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName)
2223
};
2324
}
2425

RetailCoder.VBE/Inspections/FunctionReturnValueNotUsedInspectionResult.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -34,9 +34,10 @@ public FunctionReturnValueNotUsedInspectionResult(
3434
var root = new ConvertToProcedureQuickFix(context, QualifiedSelection, returnStatements);
3535
var compositeFix = new CompositeCodeInspectionFix(root);
3636
children.ToList().ForEach(child => compositeFix.AddChild(new ConvertToProcedureQuickFix(child.Item1, child.Item2, child.Item3)));
37-
_quickFixes = new[]
37+
_quickFixes = new CodeInspectionQuickFix[]
3838
{
39-
compositeFix
39+
compositeFix,
40+
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName)
4041
};
4142
}
4243

RetailCoder.VBE/Inspections/ImplicitByRefParameterInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2626

2727
var issues = (from item in UserDeclarations
2828
where
29-
!item.IsInspectionDisabled(AnnotationName)
29+
!IsInspectionDisabled(item, AnnotationName)
3030
&& item.DeclarationType == DeclarationType.Parameter
3131
// ParamArray parameters do not allow an explicit "ByRef" parameter mechanism.
3232
&& !((ParameterDeclaration)item).IsParamArray

RetailCoder.VBE/Inspections/ImplicitPublicMemberInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,7 @@ public ImplicitPublicMemberInspection(RubberduckParserState state)
3030
public override IEnumerable<InspectionResultBase> GetInspectionResults()
3131
{
3232
var issues = from item in UserDeclarations
33-
where !item.IsInspectionDisabled(AnnotationName)
33+
where !IsInspectionDisabled(item, AnnotationName)
3434
&& ProcedureTypes.Contains(item.DeclarationType)
3535
&& item.Accessibility == Accessibility.Implicit
3636
let context = new QualifiedContext<ParserRuleContext>(item.QualifiedName, item.Context)

RetailCoder.VBE/Inspections/ImplicitVariantReturnTypeInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ public ImplicitVariantReturnTypeInspection(RubberduckParserState state)
2828
public override IEnumerable<InspectionResultBase> GetInspectionResults()
2929
{
3030
var issues = from item in UserDeclarations
31-
where !item.IsInspectionDisabled(AnnotationName)
31+
where !IsInspectionDisabled(item, AnnotationName)
3232
&& ProcedureTypes.Contains(item.DeclarationType)
3333
&& !item.IsTypeSpecified
3434
let issue = new {Declaration = item, QualifiedContext = new QualifiedContext<ParserRuleContext>(item.QualifiedName, item.Context)}

RetailCoder.VBE/Inspections/InspectionBase.cs

Lines changed: 44 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,8 @@
11
using System;
22
using System.Collections.Generic;
33
using System.Linq;
4+
using Microsoft.Vbe.Interop;
5+
using Rubberduck.Parsing.Annotations;
46
using Rubberduck.Parsing.Symbols;
57
using Rubberduck.Parsing.VBA;
68

@@ -73,20 +75,56 @@ protected InspectionBase(RubberduckParserState state, CodeInspectionSeverity def
7375
/// </summary>
7476
protected virtual IEnumerable<Declaration> Declarations
7577
{
76-
get { return State.AllDeclarations.Where(declaration => !declaration.IsInspectionDisabled(AnnotationName)); }
78+
get { return State.AllDeclarations.Where(declaration => !IsInspectionDisabled(declaration, AnnotationName)); }
79+
}
80+
81+
/// <summary>
82+
/// Gets all user declarations in the parser state without an @Ignore annotation for this inspection.
83+
/// </summary>
84+
protected virtual IEnumerable<Declaration> UserDeclarations
85+
{
86+
get { return State.AllUserDeclarations.Where(declaration => !IsInspectionDisabled(declaration, AnnotationName)); }
7787
}
7888

7989
protected virtual IEnumerable<Declaration> BuiltInDeclarations
8090
{
8191
get { return State.AllDeclarations.Where(declaration => declaration.IsBuiltIn); }
8292
}
8393

84-
/// <summary>
85-
/// Gets all user declarations in the parser state without an @Ignore annotation for this inspection.
86-
/// </summary>
87-
protected virtual IEnumerable<Declaration> UserDeclarations
94+
protected bool IsInspectionDisabled(VBComponent component, int line)
8895
{
89-
get { return State.AllUserDeclarations.Where(declaration => !declaration.IsInspectionDisabled(AnnotationName)); }
96+
var annotations = State.GetModuleAnnotations(component).ToList();
97+
98+
if (State.GetModuleAnnotations(component) == null)
99+
{
100+
return false;
101+
}
102+
103+
// VBE 1-based indexing
104+
for (var i = line - 1; i >= 1; i--)
105+
{
106+
var annotation = annotations.SingleOrDefault(a => a.QualifiedSelection.Selection.StartLine == i) as IgnoreAnnotation;
107+
if (annotation != null && annotation.InspectionNames.Contains(AnnotationName))
108+
{
109+
return true;
110+
}
111+
}
112+
113+
return false;
114+
}
115+
116+
protected bool IsInspectionDisabled(Declaration declaration, string inspectionName)
117+
{
118+
if (declaration.DeclarationType == DeclarationType.Parameter)
119+
{
120+
return declaration.ParentDeclaration.Annotations.Any(annotation =>
121+
annotation.AnnotationType == AnnotationType.Ignore
122+
&& ((IgnoreAnnotation)annotation).IsIgnored(inspectionName));
123+
}
124+
125+
return declaration.Annotations.Any(annotation =>
126+
annotation.AnnotationType == AnnotationType.Ignore
127+
&& ((IgnoreAnnotation)annotation).IsIgnored(inspectionName));
90128
}
91129

92130
public int CompareTo(IInspection other)

RetailCoder.VBE/Inspections/MoveFieldCloserToUsageInspectionResult.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,9 +15,10 @@ public class MoveFieldCloserToUsageInspectionResult : InspectionResultBase
1515
public MoveFieldCloserToUsageInspectionResult(IInspection inspection, Declaration target, RubberduckParserState state, IMessageBox messageBox)
1616
: base(inspection, target)
1717
{
18-
_quickFixes = new[]
18+
_quickFixes = new CodeInspectionQuickFix[]
1919
{
2020
new MoveFieldCloserToUsageQuickFix(target.Context, target.QualifiedSelection, target, state, messageBox),
21+
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName)
2122
};
2223
}
2324

0 commit comments

Comments
 (0)