Skip to content

Commit d3a66b4

Browse files
committed
Introduce ArgumentReference
This new subtype of IdentifierReference is used for references from arguments to the corresponding parameters. This new type extends the information passed out from the resolver in this case, e.g. with the argument position.
1 parent 6cea837 commit d3a66b4

File tree

7 files changed

+228
-31
lines changed

7 files changed

+228
-31
lines changed

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/DefaultBindingContext.cs

Lines changed: 10 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -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,7 +436,7 @@ 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

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+
}

Rubberduck.Parsing/Symbols/ParameterDeclaration.cs

Lines changed: 17 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
using System.Linq;
44
using Antlr4.Runtime;
55
using Rubberduck.Parsing.Annotations;
6+
using Rubberduck.Parsing.Binding;
67
using Rubberduck.Parsing.ComReflection;
78
using Rubberduck.Parsing.Grammar;
89
using Rubberduck.Parsing.VBA.Extensions;
@@ -123,42 +124,45 @@ public ParameterDeclaration(ComParameter parameter, Declaration parent, Qualifie
123124
public bool IsParamArray { get; set; }
124125
public string DefaultValue { get; set; } = string.Empty;
125126

126-
private ConcurrentDictionary<IdentifierReference, int> _argumentReferences = new ConcurrentDictionary<IdentifierReference, int>();
127-
public IEnumerable<IdentifierReference> ArgumentReferences => _argumentReferences.Keys;
127+
private ConcurrentDictionary<ArgumentReference, int> _argumentReferences = new ConcurrentDictionary<ArgumentReference, int>();
128+
public IEnumerable<ArgumentReference> ArgumentReferences => _argumentReferences.Keys;
128129

129130
public void AddArgumentReference(
130131
QualifiedModuleName module,
131132
Declaration scope,
132133
Declaration parent,
133-
ParserRuleContext callSiteContext,
134+
Selection argumentSelection,
135+
ParserRuleContext argumentContext,
136+
VBAParser.ArgumentListContext argumentListContext,
137+
ArgumentListArgumentType argumentType,
138+
int argumentPosition,
134139
string identifier,
135-
Declaration callee,
136-
Selection selection,
137140
IEnumerable<IParseTreeAnnotation> annotations)
138141
{
139-
var newReference = new IdentifierReference(
142+
var newReference = new ArgumentReference(
140143
module,
141144
scope,
142145
parent,
143146
identifier,
144-
selection,
145-
callSiteContext,
146-
callee,
147-
false,
148-
false,
147+
argumentSelection,
148+
argumentContext,
149+
argumentListContext,
150+
argumentType,
151+
argumentPosition,
152+
this,
149153
annotations);
150154
_argumentReferences.AddOrUpdate(newReference, 1, (key, value) => 1);
151155
}
152156

153157
public override void ClearReferences()
154158
{
155-
_argumentReferences = new ConcurrentDictionary<IdentifierReference, int>();
159+
_argumentReferences = new ConcurrentDictionary<ArgumentReference, int>();
156160
base.ClearReferences();
157161
}
158162

159163
public override void RemoveReferencesFrom(IReadOnlyCollection<QualifiedModuleName> modulesByWhichToRemoveReferences)
160164
{
161-
_argumentReferences = new ConcurrentDictionary<IdentifierReference, int>(_argumentReferences.Where(reference => !modulesByWhichToRemoveReferences.Contains(reference.Key.QualifiedModuleName)));
165+
_argumentReferences = new ConcurrentDictionary<ArgumentReference, int>(_argumentReferences.Where(reference => !modulesByWhichToRemoveReferences.Contains(reference.Key.QualifiedModuleName)));
162166
base.RemoveReferencesFrom(modulesByWhichToRemoveReferences);
163167
}
164168
}

Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs

Lines changed: 9 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -298,19 +298,20 @@ private void AddArgumentReference(
298298
Declaration parent
299299
)
300300
{
301-
var callSiteContext = argument.Context;
302-
var identifier = callSiteContext.GetText();
303-
var selection = callSiteContext.GetSelection();
304-
var callee = argument.ReferencedParameter;
301+
var argumentContext = argument.Context;
302+
var identifier = argumentContext.GetText();
303+
var argumentSelection = argumentContext.GetSelection();
305304
argument.ReferencedParameter.AddArgumentReference(
306305
module,
307306
scope,
308307
parent,
309-
callSiteContext,
308+
argumentSelection,
309+
argumentContext,
310+
argument.ArgumentListContext,
311+
argument.ArgumentType,
312+
argument.ArgumentPosition,
310313
identifier,
311-
callee,
312-
selection,
313-
FindIdentifierAnnotations(module, selection.StartLine));
314+
FindIdentifierAnnotations(module, argumentSelection.StartLine));
314315
}
315316

316317
private void AddArrayAccessReference(

Rubberduck.Refactorings/ReorderParameters/Parameter.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
using Rubberduck.Parsing.Symbols;
2-
using Rubberduck.Parsing.VBA;
32
using Rubberduck.Parsing.VBA.Extensions;
43

54
namespace Rubberduck.Refactorings.ReorderParameters

RubberduckTests/Grammar/ResolverTests.cs

Lines changed: 123 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
using Rubberduck.Parsing.VBA;
88
using RubberduckTests.Mocks;
99
using Rubberduck.Parsing.Annotations;
10+
using Rubberduck.Parsing.VBA.Extensions;
1011
using Rubberduck.VBEditor;
1112
using Rubberduck.VBEditor.SafeComWrappers;
1213
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
@@ -5629,6 +5630,49 @@ End Function
56295630
}
56305631
}
56315632

5633+
[Test]
5634+
[Category("Grammar")]
5635+
[Category("Resolver")]
5636+
[TestCase("42, a+b", "arg2", 1, 2)]
5637+
[TestCase("42, a+b", "arg1", 0, 2)]
5638+
[TestCase("arg2:=42, arg1:=a+b", "arg2", 0, 2)]
5639+
[TestCase("arg2:=42, arg1:=a+b", "arg1", 1, 2)]
5640+
[TestCase("42, a+b, (\"Hello\" & 42)", "arg3", 2, 3)]
5641+
[TestCase("42, a+b, (\"Hello\" & 42), 15+2", "furtherArgs", 3, 4)]
5642+
[TestCase("42, a+b, , (\"Hello\" & 42), 15+2", "arg3", 2, 5)]
5643+
public void CorrectArgumentReferencePositionOnMethodAccess(string arguments, string parameterName, int expectedArgumentPosition, int expectedNumberOfArguments)
5644+
{
5645+
var class1Code = @"
5646+
Public Sub Foo(arg1 As Variant, arg2 As Object, Optional arg3 As String, ParamArray furtherArgs)
5647+
End Sub
5648+
";
5649+
5650+
var moduleCode = $@"
5651+
Private Function Foo() As Variant
5652+
Dim cls As new Class1
5653+
cls.Foo({arguments})
5654+
End Function
5655+
";
5656+
5657+
var vbe = MockVbeBuilder.BuildFromModules(
5658+
("Class1", class1Code, ComponentType.ClassModule),
5659+
("Module1", moduleCode, ComponentType.StandardModule));
5660+
5661+
using (var state = Resolve(vbe.Object))
5662+
{
5663+
var parameter = state.DeclarationFinder.UserDeclarations(DeclarationType.Parameter)
5664+
.OfType<ParameterDeclaration>()
5665+
.Single(param => param.IdentifierName.Equals(parameterName));
5666+
var argumentReference = parameter.ArgumentReferences.Single();
5667+
5668+
var actualArgumentPosition = argumentReference.ArgumentPosition;
5669+
var actualNumberOfArguments = argumentReference.NumberOfArguments;
5670+
5671+
Assert.AreEqual(expectedArgumentPosition, actualArgumentPosition);
5672+
Assert.AreEqual(expectedNumberOfArguments, actualNumberOfArguments);
5673+
}
5674+
}
5675+
56325676
[Test]
56335677
[Category("Grammar")]
56345678
[Category("Resolver")]
@@ -5669,6 +5713,84 @@ End Function
56695713
}
56705714
}
56715715

5716+
[Test]
5717+
[Category("Grammar")]
5718+
[Category("Resolver")]
5719+
public void CorrectParamArrayArgumentReferencePositionOnMethodAccess()
5720+
{
5721+
var class1Code = @"
5722+
Public Sub Foo(arg1 As Variant, arg2 As Object, Optional arg3 As String = vbNullString, ParamArray furtherArgs)
5723+
End Sub
5724+
";
5725+
5726+
var moduleCode = $@"
5727+
Private Function Foo() As Variant
5728+
Dim cls As new Class1
5729+
cls.Foo(1, 2, 3, 4, 5, 6)
5730+
End Function
5731+
";
5732+
5733+
var vbe = MockVbeBuilder.BuildFromModules(
5734+
("Class1", class1Code, ComponentType.ClassModule),
5735+
("Module1", moduleCode, ComponentType.StandardModule));
5736+
5737+
using (var state = Resolve(vbe.Object))
5738+
{
5739+
var parameter = state.DeclarationFinder.UserDeclarations(DeclarationType.Parameter)
5740+
.OfType<ParameterDeclaration>()
5741+
.Single(param => param.IdentifierName.Equals("furtherArgs"));
5742+
var argumentReferences = parameter.ArgumentReferences;
5743+
5744+
var expectedPositions = new HashSet<int> { 3, 4, 5 };
5745+
var actualPositions = argumentReferences.Select(reference => reference.ArgumentPosition).ToHashSet();
5746+
5747+
var expectedPositionCount = expectedPositions.Count;
5748+
var actualPositionCount = actualPositions.Count;
5749+
5750+
Assert.AreEqual(expectedPositionCount, actualPositionCount);
5751+
expectedPositions.UnionWith(actualPositions);
5752+
Assert.AreEqual(expectedPositionCount, expectedPositions.Count);
5753+
}
5754+
}
5755+
5756+
[Test]
5757+
[Category("Grammar")]
5758+
[Category("Resolver")]
5759+
public void CorrectParamArrayArgumentReferenceArgumentCountOnMethodAccess()
5760+
{
5761+
var class1Code = @"
5762+
Public Sub Foo(arg1 As Variant, arg2 As Object, Optional arg3 As String = vbNullString, ParamArray furtherArgs)
5763+
End Sub
5764+
";
5765+
5766+
var moduleCode = $@"
5767+
Private Function Foo() As Variant
5768+
Dim cls As new Class1
5769+
cls.Foo(1, 2, 3, 4, 5, 6)
5770+
End Function
5771+
";
5772+
5773+
var vbe = MockVbeBuilder.BuildFromModules(
5774+
("Class1", class1Code, ComponentType.ClassModule),
5775+
("Module1", moduleCode, ComponentType.StandardModule));
5776+
5777+
using (var state = Resolve(vbe.Object))
5778+
{
5779+
var parameter = state.DeclarationFinder.UserDeclarations(DeclarationType.Parameter)
5780+
.OfType<ParameterDeclaration>()
5781+
.Single(param => param.IdentifierName.Equals("furtherArgs"));
5782+
var argumentReferences = parameter.ArgumentReferences;
5783+
5784+
var expectedNumberOrArguments = 6;
5785+
var actualNumberOfArgumentsValues = argumentReferences.Select(reference => reference.NumberOfArguments).ToList();
5786+
5787+
foreach (var actualNumberOfArguments in actualNumberOfArgumentsValues)
5788+
{
5789+
Assert.AreEqual(expectedNumberOrArguments, actualNumberOfArguments);
5790+
}
5791+
}
5792+
}
5793+
56725794
[Category("Grammar")]
56735795
[Category("Resolver")]
56745796
[Test]
@@ -6268,7 +6390,7 @@ End Function
62686390
[Category("Grammar")]
62696391
[Category("Resolver")]
62706392
[Test]
6271-
public void FailedDictionaryAccessExpressionWithIndexedDefaultMemberAccessHasFAiledIndexedDefaultMemberAccessOnWholeContext()
6393+
public void FailedDictionaryAccessExpressionWithIndexedDefaultMemberAccessHasFailedIndexedDefaultMemberAccessOnWholeContext()
62726394
{
62736395
var class1Code = @"
62746396
Public Function Foo(bar As String) As Class2

0 commit comments

Comments
 (0)