Skip to content

Commit 39bf194

Browse files
authored
Merge pull request #232 from rubberduck-vba/next
sync with main repo
2 parents f4d9943 + 1cec793 commit 39bf194

10 files changed

+354
-440
lines changed

RetailCoder.VBE/Inspections/AssignedByValParameterInspection.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,11 +12,13 @@ namespace Rubberduck.Inspections
1212
public sealed class AssignedByValParameterInspection : InspectionBase
1313
{
1414
private readonly IAssignedByValParameterQuickFixDialogFactory _dialogFactory;
15+
private readonly RubberduckParserState _parserState;
1516
public AssignedByValParameterInspection(RubberduckParserState state, IAssignedByValParameterQuickFixDialogFactory dialogFactory)
1617
: base(state)
1718
{
1819
Severity = DefaultSeverity;
1920
_dialogFactory = dialogFactory;
21+
_parserState = state;
2022

2123
}
2224

@@ -34,7 +36,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
3436
.ToList();
3537

3638
return parameters
37-
.Select(param => new AssignedByValParameterInspectionResult(this, param, _dialogFactory))
39+
.Select(param => new AssignedByValParameterInspectionResult(this, param, _parserState, _dialogFactory))
3840
.ToList();
3941
}
4042
}

RetailCoder.VBE/Inspections/QuickFixes/AssignedByValParameterMakeLocalCopyQuickFix.cs

Lines changed: 49 additions & 67 deletions
Original file line numberDiff line numberDiff line change
@@ -9,24 +9,26 @@
99
using Rubberduck.Common;
1010
using Antlr4.Runtime;
1111
using System.Collections.Generic;
12-
using Antlr4.Runtime.Tree;
12+
using Rubberduck.Parsing.VBA;
1313

1414
namespace Rubberduck.Inspections.QuickFixes
1515
{
1616
public class AssignedByValParameterMakeLocalCopyQuickFix : QuickFixBase
1717
{
1818
private readonly Declaration _target;
1919
private readonly IAssignedByValParameterQuickFixDialogFactory _dialogFactory;
20+
private readonly RubberduckParserState _parserState;
2021
private readonly IEnumerable<string> _forbiddenNames;
2122
private string _localCopyVariableName;
2223

23-
public AssignedByValParameterMakeLocalCopyQuickFix(Declaration target, QualifiedSelection selection, IAssignedByValParameterQuickFixDialogFactory dialogFactory)
24+
public AssignedByValParameterMakeLocalCopyQuickFix(Declaration target, QualifiedSelection selection, RubberduckParserState parserState, IAssignedByValParameterQuickFixDialogFactory dialogFactory)
2425
: base(target.Context, selection, InspectionsUI.AssignedByValParameterMakeLocalCopyQuickFix)
2526
{
2627
_target = target;
2728
_dialogFactory = dialogFactory;
28-
_forbiddenNames = GetIdentifierNamesAccessibleToProcedureContext(target.Context.Parent.Parent);
29-
_localCopyVariableName = ComputeSuggestedName();
29+
_parserState = parserState;
30+
_forbiddenNames = GetIdentifierNamesAccessibleToProcedureContext();
31+
_localCopyVariableName = ComputeSuggestedName();
3032
}
3133

3234
public override bool CanFixInModule { get { return false; } }
@@ -95,16 +97,10 @@ private void ReplaceAssignedByValParameterReferences()
9597
}
9698

9799
private void InsertLocalVariableDeclarationAndAssignment()
98-
{
99-
var block = QuickFixHelper.GetBlockStmtContextsForContext(_target.Context.Parent.Parent).FirstOrDefault();
100-
if (block == null)
101-
{
102-
return;
103-
}
104-
100+
{
105101
string[] lines = { BuildLocalCopyDeclaration(), BuildLocalCopyAssignment() };
106102
var module = Selection.QualifiedName.Component.CodeModule;
107-
module.InsertLines(block.Start.Line, lines);
103+
module.InsertLines(((VBAParser.ArgListContext)_target.Context.Parent).Stop.Line + 1, lines);
108104
}
109105

110106
private string BuildLocalCopyDeclaration()
@@ -118,74 +114,60 @@ private string BuildLocalCopyAssignment()
118114
+ _localCopyVariableName + " = " + _target.IdentifierName;
119115
}
120116

121-
private IEnumerable<string> GetIdentifierNamesAccessibleToProcedureContext(RuleContext ruleContext)
117+
private IEnumerable<string> GetIdentifierNamesAccessibleToProcedureContext()
122118
{
123-
var allIdentifiers = new HashSet<string>();
124-
125-
var blocks = QuickFixHelper.GetBlockStmtContextsForContext(ruleContext);
126-
127-
var blockStmtIdentifiers = GetIdentifierNames(blocks);
128-
allIdentifiers.UnionWith(blockStmtIdentifiers);
129-
130-
var args = QuickFixHelper.GetArgContextsForContext(ruleContext);
131-
132-
var potentiallyUnreferencedParameters = GetIdentifierNames(args);
133-
allIdentifiers.UnionWith(potentiallyUnreferencedParameters);
134-
135-
//TODO: add module and global scope variableNames to the list.
136-
137-
return allIdentifiers.ToArray();
119+
return _parserState.AllUserDeclarations
120+
.Where(candidateDeclaration =>
121+
(
122+
IsDeclarationInTheSameProcedure(candidateDeclaration, _target)
123+
|| IsDeclarationInTheSameModule(candidateDeclaration, _target)
124+
|| IsProjectGlobalDeclaration(candidateDeclaration, _target))
125+
).Select(declaration => declaration.IdentifierName).Distinct();
138126
}
139127

140-
private IEnumerable<string> GetIdentifierNames(IEnumerable<RuleContext> ruleContexts)
128+
private bool IsDeclarationInTheSameProcedure(Declaration candidateDeclaration, Declaration scopingDeclaration)
141129
{
142-
var identifiers = new HashSet<string>();
143-
foreach (var identifiersForThisContext in ruleContexts.Select(GetIdentifierNames))
144-
{
145-
identifiers.UnionWith(identifiersForThisContext);
146-
}
147-
return identifiers;
130+
return candidateDeclaration.ParentScope == scopingDeclaration.ParentScope;
148131
}
149132

150-
private static HashSet<string> GetIdentifierNames(RuleContext ruleContext)
133+
private bool IsDeclarationInTheSameModule(Declaration candidateDeclaration, Declaration scopingDeclaration)
151134
{
152-
// note: this looks like something that's already handled somewhere else...
153-
154-
//Recursively work through the tree to get all IdentifierContexts
155-
var results = new HashSet<string>();
156-
var tokenValues = typeof(Tokens).GetFields().Select(item => item.GetValue(null)).Cast<string>().Select(item => item).ToArray();
157-
var children = GetChildren(ruleContext);
135+
return candidateDeclaration.ComponentName == scopingDeclaration.ComponentName
136+
&& !IsDeclaredInMethodOrProperty(candidateDeclaration.ParentDeclaration.Context);
137+
}
158138

159-
foreach (var child in children)
160-
{
161-
var context = child as VBAParser.IdentifierContext;
162-
if (context != null)
163-
{
164-
var childName = Identifier.GetName(context);
165-
if (!tokenValues.Contains(childName))
166-
{
167-
results.Add(childName);
168-
}
169-
}
170-
else
171-
{
172-
if (!(child is TerminalNodeImpl))
173-
{
174-
results.UnionWith(GetIdentifierNames((RuleContext)child));
175-
}
176-
}
177-
}
178-
return results;
139+
private bool IsProjectGlobalDeclaration(Declaration candidateDeclaration, Declaration scopingDeclaration)
140+
{
141+
return candidateDeclaration.ProjectName == scopingDeclaration.ProjectName
142+
&& !(candidateDeclaration.ParentScopeDeclaration is ClassModuleDeclaration)
143+
&& (candidateDeclaration.Accessibility == Accessibility.Public
144+
|| ((candidateDeclaration.Accessibility == Accessibility.Implicit)
145+
&& (candidateDeclaration.ParentScopeDeclaration is ProceduralModuleDeclaration)));
179146
}
180147

181-
private static IEnumerable<IParseTree> GetChildren(IParseTree tree)
148+
private bool IsDeclaredInMethodOrProperty(RuleContext procedureContext)
182149
{
183-
var result = new List<IParseTree>();
184-
for (var index = 0; index < tree.ChildCount; index++)
150+
if (procedureContext is VBAParser.SubStmtContext)
151+
{
152+
return true;
153+
}
154+
else if (procedureContext is VBAParser.FunctionStmtContext)
155+
{
156+
return true;
157+
}
158+
else if (procedureContext is VBAParser.PropertyLetStmtContext)
159+
{
160+
return true;
161+
}
162+
else if (procedureContext is VBAParser.PropertyGetStmtContext)
163+
{
164+
return true;
165+
}
166+
else if (procedureContext is VBAParser.PropertySetStmtContext)
185167
{
186-
result.Add(tree.GetChild(index));
168+
return true;
187169
}
188-
return result;
170+
return false;
189171
}
190172
}
191173
}
Lines changed: 5 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,10 @@
1-
using Antlr4.Runtime;
21
using Rubberduck.Common;
32
using Rubberduck.Inspections.Abstract;
43
using Rubberduck.Inspections.Resources;
54
using Rubberduck.Parsing.Grammar;
65
using Rubberduck.Parsing.Symbols;
76
using Rubberduck.VBEditor;
87
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
9-
using System.Linq;
108

119
namespace Rubberduck.Inspections.QuickFixes
1210
{
@@ -15,22 +13,19 @@ namespace Rubberduck.Inspections.QuickFixes
1513
/// </summary>
1614
public class PassParameterByReferenceQuickFix : QuickFixBase
1715
{
18-
private Declaration _target;
16+
private readonly ICodeModule _codeModule;
17+
private readonly VBAParser.ArgContext _argContext;
1918

2019
public PassParameterByReferenceQuickFix(Declaration target, QualifiedSelection selection)
2120
: base(target.Context, selection, InspectionsUI.PassParameterByReferenceQuickFix)
2221
{
23-
_target = target;
22+
_argContext = target.Context as VBAParser.ArgContext;
23+
_codeModule = Selection.QualifiedName.Component.CodeModule;
2424
}
2525

2626
public override void Fix()
2727
{
28-
var module = Selection.QualifiedName.Component.CodeModule;
29-
var argContext = QuickFixHelper.GetArgContextsForContext(Context.Parent.Parent)
30-
.SingleOrDefault(parameter => Identifier.GetName(parameter.unrestrictedIdentifier())
31-
.Equals(_target.IdentifierName));
32-
33-
module.ReplaceToken(argContext.BYVAL().Symbol,Tokens.ByRef);
28+
_codeModule.ReplaceToken(_argContext.BYVAL().Symbol, Tokens.ByRef);
3429
}
3530
}
3631
}

RetailCoder.VBE/Inspections/QuickFixes/QuickFixHelper.cs

Lines changed: 0 additions & 61 deletions
This file was deleted.

RetailCoder.VBE/Inspections/Results/AssignedByValParameterInspectionResult.cs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,18 +5,21 @@
55
using Rubberduck.Inspections.Resources;
66
using Rubberduck.Parsing.Symbols;
77
using Rubberduck.UI.Refactorings;
8+
using Rubberduck.Parsing.VBA;
89

910
namespace Rubberduck.Inspections.Results
1011
{
1112
public class AssignedByValParameterInspectionResult : InspectionResultBase
1213
{
1314
private IEnumerable<QuickFixBase> _quickFixes;
15+
private readonly RubberduckParserState _parserState;
1416
private readonly IAssignedByValParameterQuickFixDialogFactory _dialogFactory;
1517

16-
public AssignedByValParameterInspectionResult(IInspection inspection, Declaration target, IAssignedByValParameterQuickFixDialogFactory dialogFactory)
18+
public AssignedByValParameterInspectionResult(IInspection inspection, Declaration target, RubberduckParserState parserState, IAssignedByValParameterQuickFixDialogFactory dialogFactory)
1719
: base(inspection, target)
1820
{
1921
_dialogFactory = dialogFactory;
22+
_parserState = parserState;
2023
}
2124

2225
public override string Description
@@ -33,7 +36,7 @@ public override IEnumerable<QuickFixBase> QuickFixes
3336
{
3437
return _quickFixes ?? (_quickFixes = new QuickFixBase[]
3538
{
36-
new AssignedByValParameterMakeLocalCopyQuickFix(Target, QualifiedSelection, _dialogFactory),
39+
new AssignedByValParameterMakeLocalCopyQuickFix(Target, QualifiedSelection, _parserState, _dialogFactory),
3740
new PassParameterByReferenceQuickFix(Target, QualifiedSelection),
3841
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName)
3942
});

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -349,7 +349,6 @@
349349
<Compile Include="Inspections\QuickFixes\AddIdentifierToWhiteListQuickFix.cs" />
350350
<Compile Include="Inspections\QuickFixes\ApplicationWorksheetFunctionQuickFix.cs" />
351351
<Compile Include="Inspections\QuickFixes\AssignedByValParameterMakeLocalCopyQuickFix.cs" />
352-
<Compile Include="Inspections\QuickFixes\QuickFixHelper.cs" />
353352
<Compile Include="Inspections\Resources\InspectionsUI.Designer.cs">
354353
<AutoGen>True</AutoGen>
355354
<DesignTime>True</DesignTime>

RetailCoder.VBE/UI/RubberduckUI.Designer.cs

Lines changed: 1 addition & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

RetailCoder.VBE/UI/RubberduckUI.resx

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1950,7 +1950,7 @@ Would you like to import them to Rubberduck?</value>
19501950
<comment>{0} = proposed variable name.</comment>
19511951
</data>
19521952
<data name="AssignedByValDialog_NewNameAlreadyUsedFormat" xml:space="preserve">
1953-
<value>'{0}' is already used in this scope.</value>
1953+
<value>'{0}' is already accessible to this scope.</value>
19541954
<comment>{0} = proposed variable name.</comment>
19551955
</data>
19561956
<data name="AssignedByValDialog_QuestionableEntryFormat" xml:space="preserve">

Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 9 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -197,7 +197,7 @@ private void CleanUpComponentAttributes(ICollection<IVBComponent> components)
197197
}
198198
}
199199

200-
private void ExecuteCommonParseActivities(List<IVBComponent> toParse, CancellationToken token)
200+
private void ExecuteCommonParseActivities(ICollection<IVBComponent> toParse, CancellationToken token)
201201
{
202202
token.ThrowIfCancellationRequested();
203203

@@ -256,7 +256,7 @@ private void RefreshDeclarationFinder()
256256
State.RefreshFinder(_hostApp);
257257
}
258258

259-
private void SetModuleStates(List<IVBComponent> components, ParserState parserState, CancellationToken token)
259+
private void SetModuleStates(ICollection<IVBComponent> components, ParserState parserState, CancellationToken token)
260260
{
261261
var options = new ParallelOptions();
262262
options.CancellationToken = token;
@@ -315,7 +315,7 @@ private void RemoveReferences(IEnumerable<Declaration> declarations, ICollection
315315
}
316316
}
317317

318-
private void ParseComponents(List<IVBComponent> components, CancellationToken token)
318+
private void ParseComponents(ICollection<IVBComponent> components, CancellationToken token)
319319
{
320320
token.ThrowIfCancellationRequested();
321321

@@ -410,7 +410,7 @@ private void ProcessComponentParseResults(IVBComponent component, Task<Component
410410
}
411411

412412

413-
private void ResolveAllDeclarations(List<IVBComponent> components, CancellationToken token)
413+
private void ResolveAllDeclarations(ICollection<IVBComponent> components, CancellationToken token)
414414
{
415415
token.ThrowIfCancellationRequested();
416416

@@ -719,7 +719,11 @@ private void ParseAllInternal(object requestor, CancellationToken token)
719719

720720
token.ThrowIfCancellationRequested();
721721

722-
var toParse = components.Where(component => State.IsNewOrModified(component)).ToList();
722+
var toParse = components.Where(component => State.IsNewOrModified(component)).ToHashSet();
723+
724+
token.ThrowIfCancellationRequested();
725+
726+
toParse.UnionWith(components.Where(component => State.GetModuleState(component) != ParserState.Ready));
723727

724728
token.ThrowIfCancellationRequested();
725729

0 commit comments

Comments
 (0)