Skip to content

Commit e07acae

Browse files
committed
added 'AllUserDeclarations' member to parser state, to return declarations where !IsBuiltIn; replaced 'AllDeclarations' and removed redundant where filters where appropriate.
1 parent e25201d commit e07acae

27 files changed

+62
-86
lines changed

RetailCoder.VBE/App.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@
1010
using Rubberduck.Common;
1111
using Rubberduck.Inspections;
1212
using Rubberduck.Parsing;
13+
using Rubberduck.Parsing.VBA;
1314
using Rubberduck.Settings;
1415
using Rubberduck.SmartIndenter;
1516
using Rubberduck.UI;
@@ -141,7 +142,7 @@ private void _stateBar_Refresh(object sender, EventArgs e)
141142
_parser.State.OnParseRequested();
142143
}
143144

144-
private void Parser_StateChanged(object sender, EventArgs e)
145+
private void Parser_StateChanged(object sender, ParserStateEventArgs e)
145146
{
146147
_appMenus.EvaluateCanExecute(_parser.State);
147148
}

RetailCoder.VBE/Inspections/AssignedByValParameterInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -27,8 +27,7 @@ public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckPars
2727
{
2828
var name = AnnotationName;
2929
var assignedByValParameters =
30-
state.AllDeclarations.Where(declaration => !declaration.IsInspectionDisabled(name)
31-
&& !declaration.IsBuiltIn
30+
state.AllUserDeclarations.Where(declaration => !declaration.IsInspectionDisabled(name)
3231
&& declaration.DeclarationType == DeclarationType.Parameter
3332
&& ((VBAParser.ArgContext)declaration.Context).BYVAL() != null
3433
&& declaration.References.Any(reference => reference.IsAssignment));

RetailCoder.VBE/Inspections/ConstantNotUsedInspection.cs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -21,10 +21,8 @@ public ConstantNotUsedInspection()
2121

2222
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
2323
{
24-
var results = state.AllDeclarations.Where(declaration =>
25-
!declaration.IsBuiltIn
26-
&& declaration.DeclarationType == DeclarationType.Constant
27-
&& !declaration.References.Any());
24+
var results = state.AllUserDeclarations.Where(declaration =>
25+
declaration.DeclarationType == DeclarationType.Constant && !declaration.References.Any());
2826

2927
return results.Select(issue =>
3028
new IdentifierNotUsedInspectionResult(this, issue, ((dynamic)issue.Context).ambiguousIdentifier(), issue.QualifiedName.QualifiedModuleName)).Cast<CodeInspectionResultBase>();

RetailCoder.VBE/Inspections/DefaultProjectNameInspection.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -25,9 +25,8 @@ public DefaultProjectNameInspection()
2525

2626
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
2727
{
28-
var issues = state.AllDeclarations
29-
.Where(declaration => !declaration.IsBuiltIn
30-
&& declaration.DeclarationType == DeclarationType.Project
28+
var issues = state.AllUserDeclarations
29+
.Where(declaration => declaration.DeclarationType == DeclarationType.Project
3130
&& declaration.IdentifierName.StartsWith("VBAProject"))
3231
.Select(issue => new DefaultProjectNameInspectionResult(this, issue, state, _wrapperFactory))
3332
.ToList();

RetailCoder.VBE/Inspections/ImplicitByRefParameterInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -26,14 +26,13 @@ public ImplicitByRefParameterInspection()
2626

2727
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
2828
{
29-
var declarations = state.AllDeclarations.ToList();
29+
var declarations = state.AllUserDeclarations.ToList();
3030

3131
var interfaceMembers = declarations.FindInterfaceImplementationMembers();
3232

3333
var issues = (from item in declarations
3434
where !item.IsInspectionDisabled(AnnotationName)
3535
&& item.DeclarationType == DeclarationType.Parameter
36-
&& !item.IsBuiltIn
3736
&& !interfaceMembers.Select(m => m.Scope).Contains(item.ParentScope)
3837
let arg = item.Context as VBAParser.ArgContext
3938
where arg != null && arg.BYREF() == null && arg.BYVAL() == null

RetailCoder.VBE/Inspections/ImplicitPublicMemberInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -34,9 +34,8 @@ public ImplicitPublicMemberInspection()
3434

3535
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
3636
{
37-
var issues = from item in state.AllDeclarations
37+
var issues = from item in state.AllUserDeclarations
3838
where !item.IsInspectionDisabled(AnnotationName)
39-
&& !item.IsBuiltIn
4039
&& ProcedureTypes.Contains(item.DeclarationType)
4140
&& item.Accessibility == Accessibility.Implicit
4241
let context = new QualifiedContext<ParserRuleContext>(item.QualifiedName, item.Context)

RetailCoder.VBE/Inspections/ImplicitVariantReturnTypeInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -32,9 +32,8 @@ public ImplicitVariantReturnTypeInspection()
3232

3333
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
3434
{
35-
var issues = from item in state.AllDeclarations
35+
var issues = from item in state.AllUserDeclarations
3636
where !item.IsInspectionDisabled(AnnotationName)
37-
&& !item.IsBuiltIn
3837
&& ProcedureTypes.Contains(item.DeclarationType)
3938
&& !item.IsTypeSpecified()
4039
let issue = new {Declaration = item, QualifiedContext = new QualifiedContext<ParserRuleContext>(item.QualifiedName, item.Context)}

RetailCoder.VBE/Inspections/Inspector.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ private void UpdateInspectionSeverity()
5151

5252
public async Task<IList<ICodeInspectionResult>> FindIssuesAsync(RubberduckParserState state, CancellationToken token)
5353
{
54-
if (state == null || !state.AllDeclarations.Any())
54+
if (state == null || !state.AllUserDeclarations.Any())
5555
{
5656
return new ICodeInspectionResult[]{};
5757
}

RetailCoder.VBE/Inspections/MultilineParameterInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ public MultilineParameterInspection()
2222

2323
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
2424
{
25-
var multilineParameters = from p in state.AllDeclarations
25+
var multilineParameters = from p in state.AllUserDeclarations
2626
.Where(item => item.DeclarationType == DeclarationType.Parameter)
2727
where p.Context.GetSelection().LineCount > 1
2828
select p;

RetailCoder.VBE/Inspections/MultipleDeclarationsInspection.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,6 @@ namespace Rubberduck.Inspections
1010
{
1111
public class MultipleDeclarationsInspection : IInspection
1212
{
13-
1413
public MultipleDeclarationsInspection()
1514
{
1615
Severity = CodeInspectionSeverity.Warning;
@@ -26,8 +25,8 @@ public MultipleDeclarationsInspection()
2625

2726
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
2827
{
29-
var issues = state.AllDeclarations
30-
.Where(item => !item.IsInspectionDisabled(AnnotationName) && !item.IsBuiltIn)
28+
var issues = state.AllUserDeclarations
29+
.Where(item => !item.IsInspectionDisabled(AnnotationName))
3130
.Where(item => item.DeclarationType == DeclarationType.Variable
3231
|| item.DeclarationType == DeclarationType.Constant)
3332
.GroupBy(variable => variable.Context.Parent as ParserRuleContext)

0 commit comments

Comments
 (0)