Skip to content

Commit 1a04e76

Browse files
authored
Merge branch 'next' into next
2 parents d654372 + ae1a780 commit 1a04e76

15 files changed

+64
-569
lines changed

RetailCoder.VBE/Inspections/EncapsulatePublicFieldInspection.cs

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -26,9 +26,18 @@ public EncapsulatePublicFieldInspection(RubberduckParserState state, IIndenter i
2626

2727
public override IEnumerable<InspectionResultBase> GetInspectionResults()
2828
{
29+
// we're creating a public field for every control on a form, needs to be ignored.
30+
var msForms = State.DeclarationFinder.FindProject("MSForms");
31+
Declaration control = null;
32+
if (msForms != null)
33+
{
34+
control = State.DeclarationFinder.FindClassModule("Control", msForms, true);
35+
}
36+
2937
var fields = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
3038
.Where(item => !IsIgnoringInspectionResultFor(item, AnnotationName)
31-
&& item.Accessibility == Accessibility.Public)
39+
&& item.Accessibility == Accessibility.Public
40+
&& (control == null || !Equals(item.AsTypeDeclaration, control)))
3241
.ToList();
3342

3443
return fields

RetailCoder.VBE/Inspections/ProcedureNotUsedInspection.cs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,9 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
4141
var handlers = State.DeclarationFinder.UserDeclarations(DeclarationType.Control)
4242
.SelectMany(control => declarations.FindEventHandlers(control)).ToList();
4343

44+
var builtInHandlers = State.AllDeclarations.FindBuiltInEventHandlers();
45+
handlers.AddRange(builtInHandlers);
46+
4447
var withEventFields = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable).Where(item => item.IsWithEvents).ToList();
4548
var withHanders = withEventFields
4649
.SelectMany(field => State.DeclarationFinder.FindHandlersForWithEventsField(field))

RetailCoder.VBE/Inspections/UseMeaningfulNameInspection.cs

Lines changed: 34 additions & 7 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 Castle.Core.Internal;
5+
using Rubberduck.Common;
46
using Rubberduck.Inspections.Abstract;
57
using Rubberduck.Inspections.Resources;
68
using Rubberduck.Inspections.Results;
@@ -27,22 +29,47 @@ public UseMeaningfulNameInspection(IMessageBox messageBox, RubberduckParserState
2729
public override string Description { get { return InspectionsUI.UseMeaningfulNameInspectionName; } }
2830
public override CodeInspectionType InspectionType { get { return CodeInspectionType.MaintainabilityAndReadabilityIssues; } }
2931

32+
private static readonly DeclarationType[] IgnoreDeclarationTypes =
33+
{
34+
DeclarationType.ModuleOption,
35+
DeclarationType.BracketedExpression,
36+
DeclarationType.LibraryFunction,
37+
DeclarationType.LibraryProcedure,
38+
};
39+
3040
public override IEnumerable<InspectionResultBase> GetInspectionResults()
3141
{
3242
var settings = _settings.Load(new CodeInspectionSettings()) ?? new CodeInspectionSettings();
33-
var whitelistedNames = settings.WhitelistedIdentifiers.Select(s => s.Identifier).ToList();
43+
var whitelistedNames = settings.WhitelistedIdentifiers.Select(s => s.Identifier).ToArray();
44+
45+
var handlers = Declarations.FindBuiltInEventHandlers();
3446

3547
var issues = UserDeclarations
36-
.Where(declaration => declaration.DeclarationType != DeclarationType.ModuleOption &&
37-
!whitelistedNames.Contains(declaration.IdentifierName) &&
38-
(declaration.IdentifierName.Length < 3 ||
39-
char.IsDigit(declaration.IdentifierName.Last()) ||
40-
!declaration.IdentifierName.Any(c =>
41-
"aeiouy".Any(a => string.Compare(a.ToString(), c.ToString(), StringComparison.OrdinalIgnoreCase) == 0))))
48+
.Where(declaration => !string.IsNullOrEmpty(declaration.IdentifierName) &&
49+
!IgnoreDeclarationTypes.Contains(declaration.DeclarationType) &&
50+
(declaration.ParentDeclaration == null ||
51+
!IgnoreDeclarationTypes.Contains(declaration.ParentDeclaration.DeclarationType) &&
52+
!handlers.Contains(declaration.ParentDeclaration)) &&
53+
!whitelistedNames.Contains(declaration.IdentifierName) &&
54+
IsBadIdentifier(declaration.IdentifierName))
4255
.Select(issue => new IdentifierNameInspectionResult(this, issue, State, _messageBox, _settings))
4356
.ToList();
4457

4558
return issues;
4659
}
60+
61+
private static bool IsBadIdentifier(string identifier)
62+
{
63+
return identifier.Length < 3 ||
64+
char.IsDigit(identifier.Last()) ||
65+
!HasVowels(identifier);
66+
}
67+
68+
private static bool HasVowels(string identifier)
69+
{
70+
const string vowels = "aeiouyàâäéèêëïîöôùûü";
71+
return identifier.Any(character => vowels.Any(vowel =>
72+
string.Compare(vowel.ToString(), character.ToString(), StringComparison.OrdinalIgnoreCase) == 0));
73+
}
4774
}
4875
}

Rubberduck.Parsing/Symbols/DeclarationLoaders/AliasDeclarations.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,7 @@ public IReadOnlyList<Declaration> Load()
5656

5757
private IReadOnlyList<Declaration> AddAliasDeclarations()
5858
{
59-
var finder = new DeclarationFinder(_state.AllDeclarations, new IAnnotation[] { });
59+
var finder = _state.DeclarationFinder;;
6060

6161
if (WeHaveAlreadyLoadedTheDeclarationsBefore(finder))
6262
{

Rubberduck.Parsing/Symbols/DeclarationLoaders/DebugDeclarations.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ public DebugDeclarations(RubberduckParserState state)
1818

1919
public IReadOnlyList<Declaration> Load()
2020
{
21-
var finder = new DeclarationFinder(_state.AllDeclarations, new IAnnotation[] { });
21+
var finder = _state.DeclarationFinder;;
2222

2323
if (WeHaveAlreadyLoadedTheDeclarationsBefore(finder))
2424
{

Rubberduck.Parsing/Symbols/DeclarationLoaders/FormEventDeclarations.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ public IReadOnlyList<Declaration> Load()
2828

2929
private static Declaration FormsClassModuleFromParserState(RubberduckParserState state)
3030
{
31-
var finder = new DeclarationFinder(state.AllDeclarations, new IAnnotation[] { });
31+
var finder = state.DeclarationFinder;
3232

3333
var msForms = finder.FindProject("MSForms");
3434
if (msForms == null)

Rubberduck.Parsing/Symbols/DeclarationLoaders/SpecialFormDeclarations.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ public SpecialFormDeclarations(RubberduckParserState state)
1919

2020
public IReadOnlyList<Declaration> Load()
2121
{
22-
var finder = new DeclarationFinder(_state.AllDeclarations, new IAnnotation[] { });
22+
var finder = _state.DeclarationFinder;
2323

2424
if (WeHaveAlreadyLoadedTheDeclarationsBefore(finder))
2525
{

Rubberduck.Parsing/Symbols/DeclarationSymbolsListener.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -69,7 +69,7 @@ public DeclarationSymbolsListener(
6969
{
7070
try
7171
{
72-
if (coclass.Key.Count != _qualifiedName.Component.Properties.Count)
72+
if (_qualifiedName.Component == null || coclass.Key.Count != _qualifiedName.Component.Properties.Count)
7373
{
7474
continue;
7575
}

Rubberduck.Parsing/Symbols/SquareBracketedNameComparer.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ public int GetHashCode(string obj)
2424

2525
private string ApplyBrackets(string value)
2626
{
27-
if (value == null) return null;
27+
if (string.IsNullOrEmpty(value)) return string.Empty;
2828

2929
return value[0] == '[' && value[value.Length - 1] == ']'
3030
? value

Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -107,7 +107,10 @@ public void Parse(CancellationTokenSource token)
107107
}
108108

109109
SyncComReferences(State.Projects);
110+
State.RefreshFinder(_hostApp);
111+
110112
AddBuiltInDeclarations();
113+
State.RefreshFinder(_hostApp);
111114

112115
foreach (var component in components)
113116
{
@@ -229,7 +232,10 @@ private void ParseAll(object requestor, CancellationTokenSource token)
229232
}
230233

231234
SyncComReferences(State.Projects);
235+
State.RefreshFinder(_hostApp);
236+
232237
AddBuiltInDeclarations();
238+
State.RefreshFinder(_hostApp);
233239

234240
// invalidation cleanup should go into ParseAsync?
235241
foreach (var key in _componentAttributes.Keys)

0 commit comments

Comments
 (0)