Skip to content

Commit

Permalink
Merge pull request #2576 from retailcoder/next
Browse files Browse the repository at this point in the history
inspection fixes
  • Loading branch information
retailcoder committed Jan 24, 2017
2 parents 693b349 + 459e7f4 commit ae1a780
Show file tree
Hide file tree
Showing 4 changed files with 16 additions and 3 deletions.
11 changes: 10 additions & 1 deletion RetailCoder.VBE/Inspections/EncapsulatePublicFieldInspection.cs
Original file line number Diff line number Diff line change
Expand Up @@ -26,9 +26,18 @@ public EncapsulatePublicFieldInspection(RubberduckParserState state, IIndenter i

public override IEnumerable<InspectionResultBase> GetInspectionResults()
{
// we're creating a public field for every control on a form, needs to be ignored.
var msForms = State.DeclarationFinder.FindProject("MSForms");
Declaration control = null;
if (msForms != null)
{
control = State.DeclarationFinder.FindClassModule("Control", msForms, true);
}

var fields = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
.Where(item => !IsIgnoringInspectionResultFor(item, AnnotationName)
&& item.Accessibility == Accessibility.Public)
&& item.Accessibility == Accessibility.Public
&& (control == null || !Equals(item.AsTypeDeclaration, control)))
.ToList();

return fields
Expand Down
3 changes: 3 additions & 0 deletions RetailCoder.VBE/Inspections/ProcedureNotUsedInspection.cs
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,9 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
var handlers = State.DeclarationFinder.UserDeclarations(DeclarationType.Control)
.SelectMany(control => declarations.FindEventHandlers(control)).ToList();

var builtInHandlers = State.AllDeclarations.FindBuiltInEventHandlers();
handlers.AddRange(builtInHandlers);

var withEventFields = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable).Where(item => item.IsWithEvents).ToList();
var withHanders = withEventFields
.SelectMany(field => State.DeclarationFinder.FindHandlersForWithEventsField(field))
Expand Down
3 changes: 2 additions & 1 deletion RetailCoder.VBE/Inspections/UseMeaningfulNameInspection.cs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
using System;
using System.Collections.Generic;
using System.Linq;
using Castle.Core.Internal;
using Rubberduck.Common;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Resources;
Expand Down Expand Up @@ -44,7 +45,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
var handlers = Declarations.FindBuiltInEventHandlers();

var issues = UserDeclarations
.Where(declaration =>
.Where(declaration => !string.IsNullOrEmpty(declaration.IdentifierName) &&
!IgnoreDeclarationTypes.Contains(declaration.DeclarationType) &&
(declaration.ParentDeclaration == null ||
!IgnoreDeclarationTypes.Contains(declaration.ParentDeclaration.DeclarationType) &&
Expand Down
2 changes: 1 addition & 1 deletion Rubberduck.Parsing/Symbols/SquareBracketedNameComparer.cs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ public int GetHashCode(string obj)

private string ApplyBrackets(string value)
{
if (value == null) return null;
if (string.IsNullOrEmpty(value)) return string.Empty;

return value[0] == '[' && value[value.Length - 1] == ']'
? value
Expand Down

0 comments on commit ae1a780

Please sign in to comment.