Skip to content

Commit 0e8690b

Browse files
authored
Merge branch 'next' into next
2 parents f377889 + 427ef60 commit 0e8690b

22 files changed

+337
-296
lines changed

RetailCoder.VBE/Inspections/Abstract/InspectionBase.cs

Lines changed: 11 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -116,28 +116,29 @@ protected bool IsIgnoringInspectionResultFor(IVBComponent component, int line)
116116

117117
protected bool IsIgnoringInspectionResultFor(Declaration declaration, string inspectionName)
118118
{
119+
var module = Declaration.GetModuleParent(declaration);
120+
if (module == null) { return false; }
121+
122+
var isIgnoredAtModuleLevel = module.Annotations
123+
.Any(annotation => annotation.AnnotationType == AnnotationType.IgnoreModule
124+
&& ((IgnoreModuleAnnotation) annotation).IsIgnored(inspectionName));
125+
126+
119127
if (declaration.DeclarationType == DeclarationType.Parameter)
120128
{
121-
return declaration.ParentDeclaration.Annotations.Any(annotation =>
129+
return isIgnoredAtModuleLevel || declaration.ParentDeclaration.Annotations.Any(annotation =>
122130
annotation.AnnotationType == AnnotationType.Ignore
123131
&& ((IgnoreAnnotation)annotation).IsIgnored(inspectionName));
124132
}
125133

126-
return declaration.Annotations.Any(annotation =>
134+
return isIgnoredAtModuleLevel || declaration.Annotations.Any(annotation =>
127135
annotation.AnnotationType == AnnotationType.Ignore
128136
&& ((IgnoreAnnotation)annotation).IsIgnored(inspectionName));
129137
}
130138

131139
protected bool IsIgnoringInspectionResultFor(IdentifierReference reference, string inspectionName)
132140
{
133-
if (reference == null)
134-
{
135-
return false;
136-
}
137-
138-
return reference.Annotations.Any(annotation =>
139-
annotation.AnnotationType == AnnotationType.Ignore
140-
&& ((IgnoreAnnotation)annotation).IsIgnored(inspectionName));
141+
return reference != null && reference.IsIgnoringInspectionResultFor(inspectionName);
141142
}
142143

143144
public int CompareTo(IInspection other)

RetailCoder.VBE/Inspections/AssignedByValParameterInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@
33
using Rubberduck.Inspections.Abstract;
44
using Rubberduck.Inspections.Resources;
55
using Rubberduck.Inspections.Results;
6-
using Rubberduck.Parsing.Grammar;
76
using Rubberduck.Parsing.Symbols;
87
using Rubberduck.Parsing.VBA;
98
using Rubberduck.UI.Refactorings;
@@ -12,7 +11,7 @@ namespace Rubberduck.Inspections
1211
{
1312
public sealed class AssignedByValParameterInspection : InspectionBase
1413
{
15-
private IAssignedByValParameterQuickFixDialogFactory _dialogFactory;
14+
private readonly IAssignedByValParameterQuickFixDialogFactory _dialogFactory;
1615
public AssignedByValParameterInspection(RubberduckParserState state, IAssignedByValParameterQuickFixDialogFactory dialogFactory)
1716
: base(state)
1817
{

RetailCoder.VBE/Inspections/QuickFixes/AssignedByValParameterMakeLocalCopyQuickFix.cs

Lines changed: 41 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
using Rubberduck.Inspections.Abstract;
22
using System.Linq;
3-
using Rubberduck.Parsing;
43
using Rubberduck.VBEditor;
54
using Rubberduck.Inspections.Resources;
65
using Rubberduck.Parsing.Grammar;
@@ -18,16 +17,16 @@ public class AssignedByValParameterMakeLocalCopyQuickFix : QuickFixBase
1817
{
1918
private readonly Declaration _target;
2019
private readonly IAssignedByValParameterQuickFixDialogFactory _dialogFactory;
20+
private readonly IEnumerable<string> _forbiddenNames;
2121
private string _localCopyVariableName;
22-
private string[] _variableNamesAccessibleToProcedureContext;
2322

2423
public AssignedByValParameterMakeLocalCopyQuickFix(Declaration target, QualifiedSelection selection, IAssignedByValParameterQuickFixDialogFactory dialogFactory)
2524
: base(target.Context, selection, InspectionsUI.AssignedByValParameterMakeLocalCopyQuickFix)
2625
{
2726
_target = target;
2827
_dialogFactory = dialogFactory;
29-
_variableNamesAccessibleToProcedureContext = GetVariableNamesAccessibleToProcedureContext(_target.Context.Parent.Parent);
30-
SetValidLocalCopyVariableNameSuggestion();
28+
_forbiddenNames = GetIdentifierNamesAccessibleToProcedureContext(target.Context.Parent.Parent);
29+
_localCopyVariableName = ComputeSuggestedName();
3130
}
3231

3332
public override bool CanFixInModule { get { return false; } }
@@ -49,10 +48,9 @@ public override void Fix()
4948

5049
private void RequestLocalCopyVariableName()
5150
{
52-
using( var view = _dialogFactory.Create(_target.IdentifierName, _target.DeclarationType.ToString()))
51+
using( var view = _dialogFactory.Create(_target.IdentifierName, _target.DeclarationType.ToString(), _forbiddenNames))
5352
{
5453
view.NewName = _localCopyVariableName;
55-
view.IdentifierNamesAlreadyDeclared = _variableNamesAccessibleToProcedureContext;
5654
view.ShowDialog();
5755
IsCancelled = view.DialogResult == DialogResult.Cancel;
5856
if (!IsCancelled)
@@ -62,63 +60,65 @@ private void RequestLocalCopyVariableName()
6260
}
6361
}
6462

65-
private void SetValidLocalCopyVariableNameSuggestion()
63+
private string ComputeSuggestedName()
6664
{
67-
_localCopyVariableName = "x" + _target.IdentifierName.CapitalizeFirstLetter();
68-
if (VariableNameIsValid(_localCopyVariableName)) { return; }
65+
var newName = "local" + _target.IdentifierName.CapitalizeFirstLetter();
66+
if (VariableNameIsValid(newName))
67+
{
68+
return newName;
69+
}
6970

70-
//If the initial suggestion is not valid, keep pre-pending x's until it is
71-
for ( int attempt = 2; attempt < 10; attempt++)
71+
for ( var attempt = 2; attempt < 10; attempt++)
7272
{
73-
_localCopyVariableName = "x" + _localCopyVariableName;
74-
if (VariableNameIsValid(_localCopyVariableName))
73+
var result = newName + attempt;
74+
if (VariableNameIsValid(result))
7575
{
76-
return;
76+
return result;
7777
}
7878
}
79-
//if "xxFoo" to "xxxxxxxxxxFoo" isn't unique, give up and go with the original suggestion.
80-
//The QuickFix will leave the code as-is unless it receives a name that is free of conflicts
81-
_localCopyVariableName = "x" + _target.IdentifierName.CapitalizeFirstLetter();
79+
return newName;
8280
}
8381

8482
private bool VariableNameIsValid(string variableName)
8583
{
86-
var validator = new VariableNameValidator(variableName);
87-
return validator.IsValidName()
88-
&& !_variableNamesAccessibleToProcedureContext
89-
.Any(name => name.Equals(variableName, System.StringComparison.InvariantCultureIgnoreCase));
84+
return VariableNameValidator.IsValidName(variableName)
85+
&& !_forbiddenNames.Any(name => name.Equals(variableName, System.StringComparison.InvariantCultureIgnoreCase));
9086
}
9187

9288
private void ReplaceAssignedByValParameterReferences()
9389
{
9490
var module = Selection.QualifiedName.Component.CodeModule;
95-
foreach (IdentifierReference identifierReference in _target.References)
91+
foreach (var identifierReference in _target.References)
9692
{
9793
module.ReplaceIdentifierReferenceName(identifierReference, _localCopyVariableName);
9894
}
9995
}
10096

10197
private void InsertLocalVariableDeclarationAndAssignment()
10298
{
103-
var blocks = QuickFixHelper.GetBlockStmtContextsForContext(_target.Context.Parent.Parent);
99+
var block = QuickFixHelper.GetBlockStmtContextsForContext(_target.Context.Parent.Parent).FirstOrDefault();
100+
if (block == null)
101+
{
102+
return;
103+
}
104+
104105
string[] lines = { BuildLocalCopyDeclaration(), BuildLocalCopyAssignment() };
105106
var module = Selection.QualifiedName.Component.CodeModule;
106-
module.InsertLines(blocks.FirstOrDefault().Start.Line, lines);
107+
module.InsertLines(block.Start.Line, lines);
107108
}
108109

109110
private string BuildLocalCopyDeclaration()
110111
{
111-
return Tokens.Dim + " " + _localCopyVariableName + " " + Tokens.As
112-
+ " " + _target.AsTypeName;
112+
return Tokens.Dim + " " + _localCopyVariableName + " " + Tokens.As + " " + _target.AsTypeName;
113113
}
114114

115115
private string BuildLocalCopyAssignment()
116116
{
117-
return (SymbolList.ValueTypes.Contains(_target.AsTypeName) ? string.Empty : Tokens.Set + " ")
117+
return (_target.AsTypeDeclaration is ClassModuleDeclaration ? Tokens.Set + " " : string.Empty)
118118
+ _localCopyVariableName + " = " + _target.IdentifierName;
119119
}
120120

121-
private string[] GetVariableNamesAccessibleToProcedureContext(RuleContext ruleContext)
121+
private IEnumerable<string> GetIdentifierNamesAccessibleToProcedureContext(RuleContext ruleContext)
122122
{
123123
var allIdentifiers = new HashSet<string>();
124124

@@ -137,29 +137,31 @@ private string[] GetVariableNamesAccessibleToProcedureContext(RuleContext ruleCo
137137
return allIdentifiers.ToArray();
138138
}
139139

140-
private HashSet<string> GetIdentifierNames(IReadOnlyList<RuleContext> ruleContexts)
140+
private IEnumerable<string> GetIdentifierNames(IEnumerable<RuleContext> ruleContexts)
141141
{
142142
var identifiers = new HashSet<string>();
143-
foreach (RuleContext ruleContext in ruleContexts)
143+
foreach (var identifiersForThisContext in ruleContexts.Select(GetIdentifierNames))
144144
{
145-
var identifiersForThisContext = GetIdentifierNames(ruleContext);
146145
identifiers.UnionWith(identifiersForThisContext);
147146
}
148147
return identifiers;
149148
}
150149

151-
private HashSet<string> GetIdentifierNames(RuleContext ruleContext)
150+
private static HashSet<string> GetIdentifierNames(RuleContext ruleContext)
152151
{
152+
// note: this looks like something that's already handled somewhere else...
153+
153154
//Recursively work through the tree to get all IdentifierContexts
154155
var results = new HashSet<string>();
155-
var tokenValues = typeof(Tokens).GetFields().Select(item => item.GetValue(null)).Cast<string>().Select(item => item);
156+
var tokenValues = typeof(Tokens).GetFields().Select(item => item.GetValue(null)).Cast<string>().Select(item => item).ToArray();
156157
var children = GetChildren(ruleContext);
157158

158-
foreach (IParseTree child in children)
159+
foreach (var child in children)
159160
{
160-
if (child is VBAParser.IdentifierContext)
161+
var context = child as VBAParser.IdentifierContext;
162+
if (context != null)
161163
{
162-
var childName = Identifier.GetName((VBAParser.IdentifierContext)child);
164+
var childName = Identifier.GetName(context);
163165
if (!tokenValues.Contains(childName))
164166
{
165167
results.Add(childName);
@@ -176,12 +178,12 @@ private HashSet<string> GetIdentifierNames(RuleContext ruleContext)
176178
return results;
177179
}
178180

179-
private static List<IParseTree> GetChildren(RuleContext ruleCtx)
181+
private static IEnumerable<IParseTree> GetChildren(IParseTree tree)
180182
{
181183
var result = new List<IParseTree>();
182-
for (int index = 0; index < ruleCtx.ChildCount; index++)
184+
for (var index = 0; index < tree.ChildCount; index++)
183185
{
184-
result.Add(ruleCtx.GetChild(index));
186+
result.Add(tree.GetChild(index));
185187
}
186188
return result;
187189
}

RetailCoder.VBE/Inspections/Results/AssignedByValParameterInspectionResult.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@ namespace Rubberduck.Inspections.Results
1111
public class AssignedByValParameterInspectionResult : InspectionResultBase
1212
{
1313
private IEnumerable<QuickFixBase> _quickFixes;
14-
private IAssignedByValParameterQuickFixDialogFactory _dialogFactory;
14+
private readonly IAssignedByValParameterQuickFixDialogFactory _dialogFactory;
1515

1616
public AssignedByValParameterInspectionResult(IInspection inspection, Declaration target, IAssignedByValParameterQuickFixDialogFactory dialogFactory)
1717
: base(inspection, target)

RetailCoder.VBE/Inspections/UseMeaningfulNameInspection.cs

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -51,17 +51,11 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
5151
!IgnoreDeclarationTypes.Contains(declaration.ParentDeclaration.DeclarationType) &&
5252
!handlers.Contains(declaration.ParentDeclaration)) &&
5353
!whitelistedNames.Contains(declaration.IdentifierName) &&
54-
IsBadIdentifier(declaration.IdentifierName))
54+
!VariableNameValidator.IsMeaningfulName(declaration.IdentifierName))
5555
.Select(issue => new IdentifierNameInspectionResult(this, issue, State, _messageBox, _settings))
5656
.ToList();
5757

5858
return issues;
5959
}
60-
61-
private static bool IsBadIdentifier(string identifier)
62-
{
63-
var validator = new VariableNameValidator(identifier);
64-
return !validator.IsMeaningfulName();
65-
}
6660
}
6761
}

0 commit comments

Comments
 (0)