Skip to content

Commit d46f190

Browse files
committed
Add support for index expressions to SetTypeResolver
1 parent 8148307 commit d46f190

File tree

3 files changed

+539
-17
lines changed

3 files changed

+539
-17
lines changed

Rubberduck.Parsing/Binding/Bindings/IndexDefaultBinding.cs

Lines changed: 26 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,8 @@
1-
using Antlr4.Runtime;
1+
using System;
2+
using Antlr4.Runtime;
23
using Rubberduck.Parsing.Symbols;
34
using System.Linq;
5+
using Rubberduck.Parsing.Grammar;
46
using Rubberduck.Parsing.VBA.DeclarationCaching;
57

68
namespace Rubberduck.Parsing.Binding
@@ -171,11 +173,11 @@ private IBoundExpression ResolveDefaultMember(IBoundExpression lExpression, stri
171173
a declared type of Variant, referencing <l-expression> with no member name.
172174
*/
173175
if (
174-
asTypeName != null
175-
&& (asTypeName.ToUpperInvariant() == "VARIANT" || asTypeName.ToUpperInvariant() == "OBJECT")
176+
(Tokens.Variant.Equals(asTypeName, StringComparison.InvariantCultureIgnoreCase)
177+
|| Tokens.Object.Equals(asTypeName, StringComparison.InvariantCultureIgnoreCase))
176178
&& !_argumentList.HasNamedArguments)
177179
{
178-
return new IndexExpression(null, ExpressionClassification.Unbound, _expression, lExpression, _argumentList);
180+
return new IndexExpression(null, ExpressionClassification.Unbound, _expression, lExpression, _argumentList, isDefaultMemberAccess: true);
179181
}
180182
/*
181183
The declared type of <l-expression> is a specific class, which has a public default Property
@@ -184,16 +186,8 @@ private IBoundExpression ResolveDefaultMember(IBoundExpression lExpression, stri
184186
if (asTypeDeclaration is ClassModuleDeclaration classModule
185187
&& classModule.DefaultMember is Declaration defaultMember)
186188
{
187-
bool isPropertyGetLetFunctionProcedure =
188-
defaultMember.DeclarationType == DeclarationType.PropertyGet
189-
|| defaultMember.DeclarationType == DeclarationType.PropertyLet
190-
|| defaultMember.DeclarationType == DeclarationType.Function
191-
|| defaultMember.DeclarationType == DeclarationType.Procedure;
192-
bool isPublic =
193-
defaultMember.Accessibility == Accessibility.Global
194-
|| defaultMember.Accessibility == Accessibility.Implicit
195-
|| defaultMember.Accessibility == Accessibility.Public;
196-
if (isPropertyGetLetFunctionProcedure && isPublic)
189+
if (IsPropertyGetLetFunctionProcedure(defaultMember)
190+
&& IsPublic(defaultMember))
197191
{
198192

199193
/*
@@ -216,7 +210,7 @@ declared type.
216210
recursively, as if this default member was specified instead for <l-expression> with the
217211
same <argument-list>.
218212
*/
219-
if (((IParameterizedDeclaration)defaultMember).Parameters.Count() == 0)
213+
if (parameters.Count(parameter => !parameter.IsOptional) == 0)
220214
{
221215
// Recursion limit reached, abort.
222216
if (DEFAULT_MEMBER_RECURSION_LIMIT == _defaultMemberRecursionLimitCounter)
@@ -245,6 +239,23 @@ declared type.
245239
return null;
246240
}
247241

242+
private static bool IsPropertyGetLetFunctionProcedure(Declaration declaration)
243+
{
244+
var declarationType = declaration.DeclarationType;
245+
return declarationType == DeclarationType.PropertyGet
246+
|| declarationType == DeclarationType.PropertyLet
247+
|| declarationType == DeclarationType.Function
248+
|| declarationType == DeclarationType.Procedure;
249+
}
250+
251+
private static bool IsPublic(Declaration declaration)
252+
{
253+
var accessibility = declaration.Accessibility;
254+
return accessibility == Accessibility.Global
255+
|| accessibility == Accessibility.Implicit
256+
|| accessibility == Accessibility.Public;
257+
}
258+
248259
private IBoundExpression ResolveLExpressionDeclaredTypeIsArray(IBoundExpression lExpression, Declaration asTypeDeclaration)
249260
{
250261
/*

Rubberduck.Parsing/TypeResolvers/SetTypeResolver.cs

Lines changed: 80 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -145,7 +145,7 @@ private static string FullObjectTypeName(Declaration setTypeDeterminingDeclarati
145145
case VBAParser.InstanceExprContext instanceExpression:
146146
return SetTypeDeterminingDeclarationOfInstance(containingModule, finder);
147147
case VBAParser.IndexExprContext indexExpression:
148-
throw new NotImplementedException();
148+
return SetTypeDeterminingDeclarationOfIndexExpression(indexExpression.lExpression(), containingModule, finder);
149149
case VBAParser.MemberAccessExprContext memberAccessExpression:
150150
return SetTypeDeterminingDeclarationOfExpression(memberAccessExpression.unrestrictedIdentifier(), containingModule, finder);
151151
case VBAParser.WithMemberAccessExprContext withMemberAccessExpression:
@@ -155,12 +155,66 @@ private static string FullObjectTypeName(Declaration setTypeDeterminingDeclarati
155155
case VBAParser.WithDictionaryAccessExprContext withDictionaryAccessExpression:
156156
return SetTypeDeterminingDeclarationOfExpression(withDictionaryAccessExpression.dictionaryAccess(), containingModule, finder);
157157
case VBAParser.WhitespaceIndexExprContext whitespaceIndexExpression:
158-
throw new NotImplementedException();
158+
return SetTypeDeterminingDeclarationOfIndexExpression(whitespaceIndexExpression.lExpression(), containingModule, finder);
159159
default:
160160
return (null, true); //We should already cover every case. Return the value indicating that we have no idea.
161161
}
162162
}
163163

164+
private (Declaration declaration, bool mightHaveSetType) SetTypeDeterminingDeclarationOfIndexExpression(VBAParser.LExpressionContext lExpression, QualifiedModuleName containingModule, DeclarationFinder finder)
165+
{
166+
var declaration = ResolveIndexExpressionAsMethod(lExpression, containingModule, finder)
167+
?? ResolveIndexExpressionAsDefaultMemberAccess(lExpression, containingModule, finder);
168+
169+
if (declaration != null)
170+
{
171+
return (declaration, MightHaveSetType(declaration));
172+
}
173+
174+
return ResolveIndexExpressionAsArrayAccess(lExpression, containingModule, finder);
175+
}
176+
177+
private Declaration ResolveIndexExpressionAsMethod(VBAParser.LExpressionContext lExpression, QualifiedModuleName containingModule, DeclarationFinder finder)
178+
{
179+
//For functions and properties, the identifier will be at the end of the lExpression.
180+
var qualifiedSelection = new QualifiedSelection(containingModule, lExpression.GetSelection().Collapse());
181+
var candidate = finder
182+
.ContainingIdentifierReferences(qualifiedSelection)
183+
.LastOrDefault()
184+
?.Declaration;
185+
return candidate?.DeclarationType.HasFlag(DeclarationType.Member) ?? false
186+
? candidate
187+
: null;
188+
}
189+
190+
private (Declaration declaration, bool mightHaveSetType) ResolveIndexExpressionAsArrayAccess(VBAParser.LExpressionContext lExpression, QualifiedModuleName containingModule, DeclarationFinder finder)
191+
{
192+
var (potentialArrayDeclaration, lExpressionMightHaveSetType) = SetTypeDeterminingDeclarationOfExpression(lExpression, containingModule, finder);
193+
194+
if (potentialArrayDeclaration == null)
195+
{
196+
return (null, lExpressionMightHaveSetType);
197+
}
198+
199+
if (!potentialArrayDeclaration.IsArray)
200+
{
201+
//This is not an array access. So, we have no idea.
202+
return (null, true);
203+
}
204+
205+
return (potentialArrayDeclaration, MightHaveSetTypeOnArrayAccess(potentialArrayDeclaration));
206+
}
207+
208+
private Declaration ResolveIndexExpressionAsDefaultMemberAccess(VBAParser.LExpressionContext lExpression, QualifiedModuleName containingModule, DeclarationFinder finder)
209+
{
210+
// A default member access references the entire lExpression.
211+
var qualifiedSelection = new QualifiedSelection(containingModule, lExpression.GetSelection());
212+
return finder
213+
.IdentifierReferences(qualifiedSelection)
214+
.FirstOrDefault(reference => reference.IsDefaultMemberAccess)
215+
?.Declaration;
216+
}
217+
164218
private (Declaration declaration, bool mightHaveSetType) SetTypeDeterminingDeclarationOfExpression(VBAParser.IdentifierContext identifier, QualifiedModuleName containingModule, DeclarationFinder finder)
165219
{
166220
var declaration = finder.IdentifierReferences(identifier, containingModule)
@@ -194,6 +248,30 @@ private static bool MightHaveSetType(Declaration declaration)
194248
|| declaration.DeclarationType.HasFlag(DeclarationType.ClassModule);
195249
}
196250

251+
private static bool MightHaveSetTypeOnArrayAccess(Declaration declaration)
252+
{
253+
return declaration == null
254+
|| IsObjectArray(declaration)
255+
|| declaration.AsTypeName == Tokens.Variant;
256+
}
257+
258+
private static bool IsObjectArray(Declaration declaration)
259+
{
260+
if (!declaration.IsArray)
261+
{
262+
return false;
263+
}
264+
265+
if (declaration.AsTypeName == Tokens.Object ||
266+
(declaration.AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.ClassModule) ?? false))
267+
{
268+
return true;
269+
}
270+
271+
return false;
272+
}
273+
274+
197275
private (Declaration declaration, bool mightHaveSetType) SetTypeDeterminingDeclarationOfInstance(QualifiedModuleName instance, DeclarationFinder finder)
198276
{
199277
var classDeclaration = finder.Classes.FirstOrDefault(cls => cls.QualifiedModuleName.Equals(instance));

0 commit comments

Comments
 (0)