Skip to content

Commit f21dc85

Browse files
authored
Merge pull request #5279 from MDoerner/FixesAroundArrayAccessReferences
Fixes around array access references
2 parents ba5dda0 + 64acbac commit f21dc85

37 files changed

+1846
-394
lines changed

Rubberduck.CodeAnalysis/QuickFixes/ChangeProcedureToFunctionQuickFix.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ public override void Fix(IInspectionResult result, IRewriteSession rewriteSessio
2323
var argIndex = parameterizedDeclaration.Parameters.ToList().IndexOf(arg);
2424

2525
UpdateSignature(result.Target, arg, rewriteSession);
26-
foreach (var reference in result.Target.References)
26+
foreach (var reference in result.Target.References.Where(reference => !reference.IsDefaultMemberAccess))
2727
{
2828
UpdateCall(reference, argIndex, rewriteSession);
2929
}

Rubberduck.CodeAnalysis/QuickFixes/ConvertToProcedureQuickFix.cs

Lines changed: 55 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -33,48 +33,88 @@ public override void Fix(IInspectionResult result, IRewriteSession rewriteSessio
3333
}
3434

3535
private void ConvertFunction(IInspectionResult result, VBAParser.FunctionStmtContext functionContext, IModuleRewriter rewriter)
36+
{
37+
RemoveAsTypeDeclaration(functionContext, rewriter);
38+
RemoveTypeHint(result, functionContext, rewriter);
39+
40+
ConvertFunctionDeclaration(functionContext, rewriter);
41+
ConvertExitFunctionStatements(functionContext, rewriter);
42+
43+
RemoveReturnStatements(result, rewriter);
44+
}
45+
46+
private static void RemoveAsTypeDeclaration(ParserRuleContext functionContext, IModuleRewriter rewriter)
3647
{
3748
var asTypeContext = functionContext.GetChild<VBAParser.AsTypeClauseContext>();
3849
if (asTypeContext != null)
3950
{
4051
rewriter.Remove(asTypeContext);
41-
rewriter.Remove(functionContext.children.ElementAt(functionContext.children.IndexOf(asTypeContext) - 1) as ParserRuleContext);
52+
rewriter.Remove(
53+
functionContext.children.ElementAt(functionContext.children.IndexOf(asTypeContext) -
54+
1) as ParserRuleContext);
4255
}
56+
}
4357

58+
private static void RemoveTypeHint(IInspectionResult result, ParserRuleContext functionContext, IModuleRewriter rewriter)
59+
{
4460
if (result.Target.TypeHint != null)
4561
{
4662
rewriter.Remove(functionContext.GetDescendent<VBAParser.TypeHintContext>());
4763
}
64+
}
4865

49-
rewriter.Replace(functionContext.FUNCTION(), Tokens.Sub);
50-
rewriter.Replace(functionContext.END_FUNCTION(), "End Sub");
51-
66+
private void RemoveReturnStatements(IInspectionResult result, IModuleRewriter rewriter)
67+
{
5268
foreach (var returnStatement in GetReturnStatements(result.Target))
5369
{
5470
rewriter.Remove(returnStatement);
5571
}
5672
}
5773

58-
private void ConvertPropertyGet(IInspectionResult result, VBAParser.PropertyGetStmtContext propertyGetContext, IModuleRewriter rewriter)
74+
private static void ConvertFunctionDeclaration(VBAParser.FunctionStmtContext functionContext, IModuleRewriter rewriter)
5975
{
60-
var asTypeContext = propertyGetContext.GetChild<VBAParser.AsTypeClauseContext>();
61-
if (asTypeContext != null)
62-
{
63-
rewriter.Remove(asTypeContext);
64-
rewriter.Remove(propertyGetContext.children.ElementAt(propertyGetContext.children.IndexOf(asTypeContext) - 1) as ParserRuleContext);
65-
}
76+
rewriter.Replace(functionContext.FUNCTION(), Tokens.Sub);
77+
rewriter.Replace(functionContext.END_FUNCTION(), "End Sub");
78+
}
6679

67-
if (result.Target.TypeHint != null)
80+
private static void ConvertExitFunctionStatements(VBAParser.FunctionStmtContext context, IModuleRewriter rewriter)
81+
{
82+
var exitStatements = context.GetDescendents<VBAParser.ExitStmtContext>();
83+
foreach (var exitStatement in exitStatements)
6884
{
69-
rewriter.Remove(propertyGetContext.GetDescendent<VBAParser.TypeHintContext>());
85+
if (exitStatement.EXIT_FUNCTION() != null)
86+
{
87+
rewriter.Replace(exitStatement, $"{Tokens.Exit} {Tokens.Sub}");
88+
}
7089
}
90+
}
91+
92+
private void ConvertPropertyGet(IInspectionResult result, VBAParser.PropertyGetStmtContext propertyGetContext, IModuleRewriter rewriter)
93+
{
94+
RemoveAsTypeDeclaration(propertyGetContext, rewriter);
95+
RemoveTypeHint(result, propertyGetContext, rewriter);
7196

97+
ConvertPropertyGetDeclaration(propertyGetContext, rewriter);
98+
ConvertExitPropertyStatements(propertyGetContext, rewriter);
99+
100+
RemoveReturnStatements(result, rewriter);
101+
}
102+
103+
private static void ConvertPropertyGetDeclaration(VBAParser.PropertyGetStmtContext propertyGetContext, IModuleRewriter rewriter)
104+
{
72105
rewriter.Replace(propertyGetContext.PROPERTY_GET(), Tokens.Sub);
73106
rewriter.Replace(propertyGetContext.END_PROPERTY(), "End Sub");
107+
}
74108

75-
foreach (var returnStatement in GetReturnStatements(result.Target))
109+
private static void ConvertExitPropertyStatements(VBAParser.PropertyGetStmtContext context, IModuleRewriter rewriter)
110+
{
111+
var exitStatements = context.GetDescendents<VBAParser.ExitStmtContext>();
112+
foreach (var exitStatement in exitStatements)
76113
{
77-
rewriter.Remove(returnStatement);
114+
if (exitStatement.EXIT_PROPERTY() != null)
115+
{
116+
rewriter.Replace(exitStatement, $"{Tokens.Exit} {Tokens.Sub}");
117+
}
78118
}
79119
}
80120

Rubberduck.CodeAnalysis/QuickFixes/IntroduceLocalVariableQuickFix.cs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -22,10 +22,10 @@ public IntroduceLocalVariableQuickFix()
2222
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
2323
{
2424
var identifierContext = result.Target.Context;
25-
var enclosingStatmentContext = identifierContext.GetAncestor<VBAParser.BlockStmtContext>();
26-
var instruction = IdentifierDeclarationText(result.Target.IdentifierName, EndOfStatementText(enclosingStatmentContext), FrontPadding(enclosingStatmentContext));
25+
var enclosingStatementContext = identifierContext.GetAncestor<VBAParser.BlockStmtContext>();
26+
var instruction = IdentifierDeclarationText(result.Target.IdentifierName, EndOfStatementText(enclosingStatementContext), FrontPadding(enclosingStatementContext));
2727
var rewriter = rewriteSession.CheckOutModuleRewriter(result.Target.QualifiedModuleName);
28-
rewriter.InsertBefore(enclosingStatmentContext.Start.TokenIndex, instruction);
28+
rewriter.InsertBefore(enclosingStatementContext.Start.TokenIndex, instruction);
2929
}
3030

3131
private string EndOfStatementText(VBAParser.BlockStmtContext context)

Rubberduck.Core/UI/Controls/FindAllReferencesService.cs

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -141,11 +141,14 @@ private SearchResultsViewModel CreateViewModel(ProjectDeclaration project, Proje
141141

142142
private SearchResultsViewModel CreateViewModel(Declaration declaration)
143143
{
144-
var results = declaration.References.Distinct().Select(reference =>
145-
new SearchResultItem(
146-
reference.ParentNonScoping,
147-
new NavigateCodeEventArgs(reference.QualifiedModuleName, reference.Selection),
148-
GetModuleLine(reference.QualifiedModuleName, reference.Selection.StartLine)));
144+
var results = declaration.References
145+
.Where(reference => !reference.IsArrayAccess)
146+
.Distinct()
147+
.Select(reference =>
148+
new SearchResultItem(
149+
reference.ParentNonScoping,
150+
new NavigateCodeEventArgs(reference.QualifiedModuleName, reference.Selection),
151+
GetModuleLine(reference.QualifiedModuleName, reference.Selection.StartLine)));
149152

150153
var accessor = declaration.DeclarationType.HasFlag(DeclarationType.PropertyGet) ? "(get)"
151154
: declaration.DeclarationType.HasFlag(DeclarationType.PropertyLet) ? "(let)"

Rubberduck.Parsing/Binding/ArgumentListArgument.cs

Lines changed: 20 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -12,15 +12,26 @@ public sealed class ArgumentListArgument
1212
private readonly Func<Declaration, IBoundExpression> _namedArgumentExpressionCreator;
1313
private readonly bool _isAddressOfArgument;
1414

15-
public ArgumentListArgument(IExpressionBinding binding, ParserRuleContext context, ArgumentListArgumentType argumentType, bool isAddressOfArgument = false)
16-
: this (binding, context, argumentType, calledProcedure => null, isAddressOfArgument)
17-
{
18-
}
15+
public ArgumentListArgument(
16+
IExpressionBinding binding,
17+
ParserRuleContext context,
18+
VBAParser.ArgumentListContext argumentListContext,
19+
ArgumentListArgumentType argumentType,
20+
bool isAddressOfArgument = false)
21+
: this (binding, context, argumentListContext, argumentType, calledProcedure => null, isAddressOfArgument)
22+
{}
1923

20-
public ArgumentListArgument(IExpressionBinding binding, ParserRuleContext context, ArgumentListArgumentType argumentType, Func<Declaration, IBoundExpression> namedArgumentExpressionCreator, bool isAddressOfArgument = false)
24+
public ArgumentListArgument(
25+
IExpressionBinding binding,
26+
ParserRuleContext context,
27+
VBAParser.ArgumentListContext argumentListContext,
28+
ArgumentListArgumentType argumentType,
29+
Func<Declaration, IBoundExpression> namedArgumentExpressionCreator,
30+
bool isAddressOfArgument = false)
2131
{
2232
_binding = binding;
2333
Context = context;
34+
ArgumentListContext = argumentListContext;
2435
ArgumentType = argumentType;
2536
_namedArgumentExpressionCreator = namedArgumentExpressionCreator;
2637
_isAddressOfArgument = isAddressOfArgument;
@@ -31,10 +42,14 @@ public ArgumentListArgument(IExpressionBinding binding, ParserRuleContext contex
3142
public IBoundExpression NamedArgumentExpression { get; private set; }
3243
public IBoundExpression Expression { get; private set; }
3344
public ParameterDeclaration ReferencedParameter { get; private set; }
45+
public int ArgumentPosition { get; private set; }
3446
public ParserRuleContext Context { get; }
47+
public VBAParser.ArgumentListContext ArgumentListContext { get; }
3548

3649
public void Resolve(Declaration calledProcedure, int parameterIndex, bool isArrayAccess = false)
3750
{
51+
ArgumentPosition = parameterIndex;
52+
3853
var binding = _binding;
3954
if (calledProcedure != null)
4055
{

Rubberduck.Parsing/Binding/Bindings/LetCoercionDefaultBinding.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -114,7 +114,7 @@ private static IBoundExpression ResolveViaDefaultMember(IBoundExpression wrapped
114114
&& defaultMember.DeclarationType == DeclarationType.PropertyLet
115115
&& IsCompatibleWithOneNonObjectParameter(parameters))
116116
{
117-
//This is a Let assignment. So, finding a Property Let with one non object paramter means we are done.
117+
//This is a Let assignment. So, finding a Property Let with one non object parameter means we are done.
118118
return new LetCoercionDefaultMemberAccessExpression(defaultMember, defaultMemberClassification, expression, wrappedExpression, recursionDepth, containedExpression);
119119
}
120120

Rubberduck.Parsing/Binding/Bindings/NewTypeBinding.cs

Lines changed: 0 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -1,29 +1,16 @@
11
using Antlr4.Runtime;
2-
using Rubberduck.Parsing.Symbols;
3-
using Rubberduck.Parsing.VBA.DeclarationCaching;
42

53
namespace Rubberduck.Parsing.Binding
64
{
75
public sealed class NewTypeBinding : IExpressionBinding
86
{
9-
private readonly DeclarationFinder _declarationFinder;
10-
private readonly Declaration _project;
11-
private readonly Declaration _module;
12-
private readonly Declaration _parent;
137
private readonly ParserRuleContext _expression;
148
private readonly IExpressionBinding _typeExpressionBinding;
159

1610
public NewTypeBinding(
17-
DeclarationFinder declarationFinder,
18-
Declaration module,
19-
Declaration parent,
2011
ParserRuleContext expression,
2112
IExpressionBinding typeExpressionBinding)
2213
{
23-
_declarationFinder = declarationFinder;
24-
_project = module.ParentDeclaration;
25-
_module = module;
26-
_parent = parent;
2714
_expression = expression;
2815
_typeExpressionBinding = typeExpressionBinding;
2916
}

Rubberduck.Parsing/Binding/DefaultBindingContext.cs

Lines changed: 15 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -198,7 +198,7 @@ private IExpressionBinding Visit(Declaration module, Declaration parent, VBAPars
198198
{
199199
return null;
200200
}
201-
return new NewTypeBinding(_declarationFinder, module, parent, expression, typeExpressionBinding);
201+
return new NewTypeBinding(expression, typeExpressionBinding);
202202
}
203203

204204
private IExpressionBinding Visit(Declaration module, Declaration parent, VBAParser.MarkedFileNumberExprContext expression, IBoundExpression withBlockVariable)
@@ -325,14 +325,20 @@ private ArgumentList VisitArgumentList(Declaration module, Declaration parent, V
325325
if (expr.positionalArgument() != null)
326326
{
327327
var (binding, context, isAddressOfArgument) = VisitArgumentBinding(module, parent, expr.positionalArgument().argumentExpression(), withBlockVariable);
328-
convertedList.AddArgument(new ArgumentListArgument(binding, context, ArgumentListArgumentType.Positional, isAddressOfArgument));
328+
convertedList.AddArgument(new ArgumentListArgument(
329+
binding,
330+
context,
331+
argumentList,
332+
ArgumentListArgumentType.Positional,
333+
isAddressOfArgument));
329334
}
330335
else if (expr.namedArgument() != null)
331336
{
332337
var (binding, context, isAddressOfArgument) = VisitArgumentBinding(module, parent, expr.namedArgument().argumentExpression(), withBlockVariable);
333338
convertedList.AddArgument(new ArgumentListArgument(
334339
binding,
335340
context,
341+
argumentList,
336342
ArgumentListArgumentType.Named,
337343
CreateNamedArgumentExpressionCreator(expr.namedArgument().unrestrictedIdentifier().GetText(), expr.namedArgument().unrestrictedIdentifier()),
338344
isAddressOfArgument));
@@ -344,6 +350,7 @@ private ArgumentList VisitArgumentList(Declaration module, Declaration parent, V
344350
convertedList.AddArgument(new ArgumentListArgument(
345351
binding,
346352
missingArgumentContext,
353+
argumentList,
347354
ArgumentListArgumentType.Missing,
348355
false));
349356
}
@@ -415,7 +422,7 @@ declared type of String and a value equal to the name value of <unrestricted-nam
415422
Still, we have a specific binding for it in order to attach a reference to the called default member to the exclamation mark.
416423
*/
417424
var fakeArgList = new ArgumentList();
418-
fakeArgList.AddArgument(new ArgumentListArgument(new LiteralDefaultBinding(nameContext), nameContext, ArgumentListArgumentType.Positional));
425+
fakeArgList.AddArgument(new ArgumentListArgument(new LiteralDefaultBinding(nameContext), nameContext, null, ArgumentListArgumentType.Positional));
419426
return new DictionaryAccessDefaultBinding(expression, lExpressionBinding, fakeArgList);
420427
}
421428

@@ -429,12 +436,16 @@ declared type of String and a value equal to the name value of <unrestricted-nam
429436
Still, we have a specific binding for it in order to attach a reference to the called default member to the exclamation mark.
430437
*/
431438
var fakeArgList = new ArgumentList();
432-
fakeArgList.AddArgument(new ArgumentListArgument(new LiteralDefaultBinding(nameContext), nameContext, ArgumentListArgumentType.Positional));
439+
fakeArgList.AddArgument(new ArgumentListArgument(new LiteralDefaultBinding(nameContext), nameContext, null, ArgumentListArgumentType.Positional));
433440
return new DictionaryAccessDefaultBinding(expression, lExpression, fakeArgList);
434441
}
435442

436443
private IExpressionBinding Visit(Declaration module, Declaration parent, VBAParser.WithMemberAccessExprContext expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext)
437444
{
445+
if (withBlockVariable == null)
446+
{
447+
withBlockVariable = new ResolutionFailedExpression(expression);
448+
}
438449
return new MemberAccessDefaultBinding(_declarationFinder, Declaration.GetProjectParent(parent), module, parent, expression, withBlockVariable, expression.unrestrictedIdentifier().GetText(), statementContext, expression.unrestrictedIdentifier());
439450
}
440451

Lines changed: 49 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,49 @@
1+
using System.Collections.Generic;
2+
using Antlr4.Runtime;
3+
using Rubberduck.Parsing.Annotations;
4+
using Rubberduck.Parsing.Binding;
5+
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.VBEditor;
7+
8+
namespace Rubberduck.Parsing.Symbols
9+
{
10+
public class ArgumentReference : IdentifierReference
11+
{
12+
public ArgumentReference(
13+
QualifiedModuleName qualifiedName,
14+
Declaration parentScopingDeclaration,
15+
Declaration parentNonScopingDeclaration,
16+
string identifierName,
17+
Selection argumentSelection,
18+
ParserRuleContext context,
19+
VBAParser.ArgumentListContext argumentListContext,
20+
ArgumentListArgumentType argumentType,
21+
int argumentPosition,
22+
ParameterDeclaration referencedParameter,
23+
IEnumerable<IParseTreeAnnotation> annotations = null)
24+
: base(
25+
qualifiedName,
26+
parentScopingDeclaration,
27+
parentNonScopingDeclaration,
28+
identifierName,
29+
argumentSelection,
30+
context,
31+
referencedParameter,
32+
false,
33+
false,
34+
annotations)
35+
{
36+
ArgumentType = argumentType;
37+
ArgumentPosition = argumentPosition;
38+
ArgumentListContext = argumentListContext;
39+
NumberOfArguments = ArgumentListContext?.argument()?.Length ?? 0;
40+
ArgumentListSelection = argumentListContext?.GetSelection() ?? Selection.Empty;
41+
}
42+
43+
public ArgumentListArgumentType ArgumentType { get; }
44+
public int ArgumentPosition { get; }
45+
public int NumberOfArguments { get; }
46+
public VBAParser.ArgumentListContext ArgumentListContext { get; }
47+
public Selection ArgumentListSelection { get; }
48+
}
49+
}

0 commit comments

Comments
 (0)