3
3
using System . Linq ;
4
4
using Antlr4 . Runtime ;
5
5
using Antlr4 . Runtime . Tree ;
6
+ using Microsoft . Vbe . Interop ;
6
7
using Rubberduck . Parsing . Grammar ;
7
8
8
9
namespace Rubberduck . Parsing . Symbols
@@ -13,6 +14,7 @@ public class IdentifierReferenceListener : VBABaseListener
13
14
private readonly QualifiedModuleName _qualifiedName ;
14
15
15
16
private string _currentScope ;
17
+ private DeclarationType _currentScopeType ;
16
18
17
19
public IdentifierReferenceListener ( VBComponentParseResult result , Declarations declarations )
18
20
: this ( result . QualifiedName , declarations )
@@ -33,15 +35,19 @@ public IdentifierReferenceListener(QualifiedModuleName qualifiedName, Declaratio
33
35
private void SetCurrentScope ( )
34
36
{
35
37
_currentScope = ModuleScope ;
38
+ _currentScopeType = _qualifiedName . Component . Type == vbext_ComponentType . vbext_ct_StdModule
39
+ ? DeclarationType . Module
40
+ : DeclarationType . Class ;
36
41
}
37
42
38
43
/// <summary>
39
44
/// Sets current scope to specified module member.
40
45
/// </summary>
41
46
/// <param name="name">The name of the member owning the current scope.</param>
42
- private void SetCurrentScope ( string name )
47
+ private void SetCurrentScope ( string name , DeclarationType scopeType )
43
48
{
44
49
_currentScope = _qualifiedName + "." + name ;
50
+ _currentScopeType = scopeType ;
45
51
}
46
52
47
53
public override void EnterLiteral ( VBAParser . LiteralContext context )
@@ -81,7 +87,7 @@ private void HandleNumberLiteral(ITerminalNode numberLiteral)
81
87
82
88
public override void EnterSubStmt ( VBAParser . SubStmtContext context )
83
89
{
84
- SetCurrentScope ( context . ambiguousIdentifier ( ) . GetText ( ) ) ;
90
+ SetCurrentScope ( context . ambiguousIdentifier ( ) . GetText ( ) , DeclarationType . Procedure ) ;
85
91
}
86
92
87
93
public override void ExitSubStmt ( VBAParser . SubStmtContext context )
@@ -91,7 +97,7 @@ public override void ExitSubStmt(VBAParser.SubStmtContext context)
91
97
92
98
public override void EnterFunctionStmt ( VBAParser . FunctionStmtContext context )
93
99
{
94
- SetCurrentScope ( context . ambiguousIdentifier ( ) . GetText ( ) ) ;
100
+ SetCurrentScope ( context . ambiguousIdentifier ( ) . GetText ( ) , DeclarationType . Function ) ;
95
101
}
96
102
97
103
public override void ExitFunctionStmt ( VBAParser . FunctionStmtContext context )
@@ -101,7 +107,7 @@ public override void ExitFunctionStmt(VBAParser.FunctionStmtContext context)
101
107
102
108
public override void EnterPropertyGetStmt ( VBAParser . PropertyGetStmtContext context )
103
109
{
104
- SetCurrentScope ( context . ambiguousIdentifier ( ) . GetText ( ) ) ;
110
+ SetCurrentScope ( context . ambiguousIdentifier ( ) . GetText ( ) , DeclarationType . PropertyGet ) ;
105
111
}
106
112
107
113
public override void ExitPropertyGetStmt ( VBAParser . PropertyGetStmtContext context )
@@ -111,7 +117,7 @@ public override void ExitPropertyGetStmt(VBAParser.PropertyGetStmtContext contex
111
117
112
118
public override void EnterPropertyLetStmt ( VBAParser . PropertyLetStmtContext context )
113
119
{
114
- SetCurrentScope ( context . ambiguousIdentifier ( ) . GetText ( ) ) ;
120
+ SetCurrentScope ( context . ambiguousIdentifier ( ) . GetText ( ) , DeclarationType . PropertyLet ) ;
115
121
}
116
122
117
123
public override void ExitPropertyLetStmt ( VBAParser . PropertyLetStmtContext context )
@@ -121,7 +127,7 @@ public override void ExitPropertyLetStmt(VBAParser.PropertyLetStmtContext contex
121
127
122
128
public override void EnterPropertySetStmt ( VBAParser . PropertySetStmtContext context )
123
129
{
124
- SetCurrentScope ( context . ambiguousIdentifier ( ) . GetText ( ) ) ;
130
+ SetCurrentScope ( context . ambiguousIdentifier ( ) . GetText ( ) , DeclarationType . PropertySet ) ;
125
131
}
126
132
127
133
public override void ExitPropertySetStmt ( VBAParser . PropertySetStmtContext context )
@@ -153,15 +159,15 @@ public override void EnterSetStmt(VBAParser.SetStmtContext context)
153
159
private VBAParser . AmbiguousIdentifierContext FindAssignmentTarget ( VBAParser . ImplicitCallStmt_InStmtContext leftSide , DeclarationType accessorType )
154
160
{
155
161
VBAParser . AmbiguousIdentifierContext context ;
156
- var call = Resolve ( leftSide . iCS_S_ProcedureOrArrayCall ( ) , out context )
157
- ?? Resolve ( leftSide . iCS_S_VariableOrProcedureCall ( ) , out context )
158
- ?? Resolve ( leftSide . iCS_S_DictionaryCall ( ) , out context )
159
- ?? Resolve ( leftSide . iCS_S_MembersCall ( ) , out context ) ;
162
+ var call = Resolve ( leftSide . iCS_S_ProcedureOrArrayCall ( ) , out context , accessorType )
163
+ ?? Resolve ( leftSide . iCS_S_VariableOrProcedureCall ( ) , out context , accessorType )
164
+ ?? Resolve ( leftSide . iCS_S_DictionaryCall ( ) , out context , accessorType )
165
+ ?? Resolve ( leftSide . iCS_S_MembersCall ( ) , out context , accessorType ) ;
160
166
161
167
return context ;
162
168
}
163
169
164
- private VBAParser . AmbiguousIdentifierContext EnterDictionaryCall ( VBAParser . DictionaryCallStmtContext dictionaryCall , VBAParser . AmbiguousIdentifierContext parentIdentifier = null )
170
+ private VBAParser . AmbiguousIdentifierContext EnterDictionaryCall ( VBAParser . DictionaryCallStmtContext dictionaryCall , VBAParser . AmbiguousIdentifierContext parentIdentifier = null , DeclarationType accessorType = DeclarationType . PropertyGet )
165
171
{
166
172
if ( dictionaryCall == null )
167
173
{
@@ -170,7 +176,8 @@ private VBAParser.AmbiguousIdentifierContext EnterDictionaryCall(VBAParser.Dicti
170
176
171
177
if ( parentIdentifier != null )
172
178
{
173
- if ( ! EnterIdentifier ( parentIdentifier , parentIdentifier . GetSelection ( ) ) )
179
+ var isTarget = accessorType == DeclarationType . PropertyLet || accessorType == DeclarationType . PropertySet ;
180
+ if ( ! EnterIdentifier ( parentIdentifier , parentIdentifier . GetSelection ( ) , isTarget , accessorType : accessorType ) )
174
181
// we're referencing "member" in "member!field"
175
182
{
176
183
return null ;
@@ -306,7 +313,7 @@ public override void ExitWithStmt(VBAParser.WithStmtContext context)
306
313
_withQualifiers . Pop ( ) ;
307
314
}
308
315
309
- private Declaration Resolve ( VBAParser . ICS_S_ProcedureOrArrayCallContext context , out VBAParser . AmbiguousIdentifierContext identifierContext )
316
+ private Declaration Resolve ( VBAParser . ICS_S_ProcedureOrArrayCallContext context , out VBAParser . AmbiguousIdentifierContext identifierContext , DeclarationType accessorType )
310
317
{
311
318
if ( context == null )
312
319
{
@@ -318,7 +325,7 @@ private Declaration Resolve(VBAParser.ICS_S_ProcedureOrArrayCallContext context,
318
325
var name = identifier . GetText ( ) ;
319
326
320
327
var procedure = FindProcedureDeclaration ( name , identifier ) ;
321
- var result = procedure ?? FindVariableDeclaration ( name , identifier ) ;
328
+ var result = procedure ?? FindVariableDeclaration ( name , identifier , accessorType ) ;
322
329
323
330
identifierContext = result == null
324
331
? null
@@ -331,10 +338,10 @@ private Declaration Resolve(VBAParser.ICS_S_ProcedureOrArrayCallContext context,
331
338
private Declaration Resolve ( VBAParser . ICS_S_ProcedureOrArrayCallContext context )
332
339
{
333
340
VBAParser . AmbiguousIdentifierContext discarded ;
334
- return Resolve ( context , out discarded ) ;
341
+ return Resolve ( context , out discarded , DeclarationType . PropertyGet ) ;
335
342
}
336
343
337
- private Declaration Resolve ( VBAParser . ICS_S_VariableOrProcedureCallContext context , out VBAParser . AmbiguousIdentifierContext identifierContext )
344
+ private Declaration Resolve ( VBAParser . ICS_S_VariableOrProcedureCallContext context , out VBAParser . AmbiguousIdentifierContext identifierContext , DeclarationType accessorType )
338
345
{
339
346
if ( context == null )
340
347
{
@@ -345,8 +352,8 @@ private Declaration Resolve(VBAParser.ICS_S_VariableOrProcedureCallContext conte
345
352
var identifier = context . ambiguousIdentifier ( ) ;
346
353
var name = identifier . GetText ( ) ;
347
354
348
- var procedure = FindProcedureDeclaration ( name , identifier ) ;
349
- var result = procedure ?? FindVariableDeclaration ( name , identifier ) ;
355
+ var procedure = FindProcedureDeclaration ( name , identifier , accessorType ) ;
356
+ var result = procedure ?? FindVariableDeclaration ( name , identifier , accessorType ) ;
350
357
351
358
identifierContext = result == null
352
359
? null
@@ -359,21 +366,21 @@ private Declaration Resolve(VBAParser.ICS_S_VariableOrProcedureCallContext conte
359
366
private Declaration Resolve ( VBAParser . ICS_S_VariableOrProcedureCallContext context )
360
367
{
361
368
VBAParser . AmbiguousIdentifierContext discarded ;
362
- return Resolve ( context , out discarded ) ;
369
+ return Resolve ( context , out discarded , DeclarationType . PropertyGet ) ;
363
370
}
364
371
365
- private Declaration Resolve ( VBAParser . ICS_S_DictionaryCallContext context , out VBAParser . AmbiguousIdentifierContext identifierContext , VBAParser . AmbiguousIdentifierContext parentIdentifier = null )
372
+ private Declaration Resolve ( VBAParser . ICS_S_DictionaryCallContext context , out VBAParser . AmbiguousIdentifierContext identifierContext , DeclarationType accessorType , VBAParser . AmbiguousIdentifierContext parentIdentifier = null )
366
373
{
367
374
if ( context == null )
368
375
{
369
376
identifierContext = null ;
370
377
return null ;
371
378
}
372
379
373
- var identifier = EnterDictionaryCall ( context . dictionaryCallStmt ( ) , parentIdentifier ) ;
380
+ var identifier = EnterDictionaryCall ( context . dictionaryCallStmt ( ) , parentIdentifier , accessorType ) ;
374
381
var name = identifier . GetText ( ) ;
375
382
376
- var result = FindVariableDeclaration ( name , identifier ) ;
383
+ var result = FindVariableDeclaration ( name , identifier , accessorType ) ;
377
384
378
385
identifierContext = result == null
379
386
? null
@@ -386,10 +393,10 @@ private Declaration Resolve(VBAParser.ICS_S_DictionaryCallContext context, out V
386
393
private Declaration Resolve ( VBAParser . ICS_S_DictionaryCallContext context , VBAParser . AmbiguousIdentifierContext parentIdentifier = null )
387
394
{
388
395
VBAParser . AmbiguousIdentifierContext discarded ;
389
- return Resolve ( context , out discarded , parentIdentifier ) ;
396
+ return Resolve ( context , out discarded , DeclarationType . PropertyGet , parentIdentifier ) ;
390
397
}
391
398
392
- private Declaration Resolve ( VBAParser . ICS_S_MembersCallContext context , out VBAParser . AmbiguousIdentifierContext identifierContext )
399
+ private Declaration Resolve ( VBAParser . ICS_S_MembersCallContext context , out VBAParser . AmbiguousIdentifierContext identifierContext , DeclarationType accessorType )
393
400
{
394
401
if ( context == null )
395
402
{
@@ -434,7 +441,7 @@ private Declaration Resolve(VBAParser.ICS_S_MembersCallContext context, out VBAP
434
441
private Declaration Resolve ( VBAParser . ICS_S_MembersCallContext context )
435
442
{
436
443
VBAParser . AmbiguousIdentifierContext discarded ;
437
- return Resolve ( context , out discarded ) ;
444
+ return Resolve ( context , out discarded , DeclarationType . PropertyGet ) ;
438
445
}
439
446
440
447
private Declaration Resolve ( VBAParser . ICS_B_MemberProcedureCallContext context )
@@ -469,7 +476,7 @@ public override void EnterVsAssign(VBAParser.VsAssignContext context)
469
476
var callStatementB = context . Parent . Parent . Parent as VBAParser . ICS_S_VariableOrProcedureCallContext ;
470
477
var callStatementC = context . Parent . Parent . Parent as VBAParser . ICS_B_MemberProcedureCallContext ;
471
478
var callStatementD = context . Parent . Parent . Parent as VBAParser . ICS_B_ProcedureCallContext ;
472
-
479
+
473
480
var procedureName = string . Empty ;
474
481
ParserRuleContext identifierContext = null ;
475
482
if ( callStatementA != null )
@@ -545,13 +552,13 @@ private Declaration FindProcedureDeclaration(string procedureName, ParserRuleCon
545
552
return procedure ;
546
553
}
547
554
548
- private Declaration FindVariableDeclaration ( string procedureName , ParserRuleContext context )
555
+ private Declaration FindVariableDeclaration ( string procedureName , ParserRuleContext context , DeclarationType accessorType )
549
556
{
550
557
var matches = _declarations [ procedureName ]
551
558
. Where ( declaration => declaration . DeclarationType == DeclarationType . Variable || declaration . DeclarationType == DeclarationType . Parameter )
552
559
. Where ( IsInScope ) ;
553
560
554
- var variable = GetClosestScopeDeclaration ( matches , context ) ;
561
+ var variable = GetClosestScopeDeclaration ( matches , context , accessorType ) ;
555
562
return variable ;
556
563
}
557
564
@@ -602,6 +609,13 @@ private bool IsInScope(Declaration declaration)
602
609
|| IsGlobalProcedure ( declaration ) ;
603
610
}
604
611
612
+ private static readonly Type [ ] PropertyContexts =
613
+ {
614
+ typeof ( VBAParser . PropertyGetStmtContext ) ,
615
+ typeof ( VBAParser . PropertyLetStmtContext ) ,
616
+ typeof ( VBAParser . PropertySetStmtContext )
617
+ } ;
618
+
605
619
private Declaration GetClosestScopeDeclaration ( IEnumerable < Declaration > declarations , ParserRuleContext context , DeclarationType accessorType = DeclarationType . PropertyGet )
606
620
{
607
621
if ( context . Parent . Parent . Parent is VBAParser . AsTypeClauseContext )
@@ -615,11 +629,19 @@ private Declaration GetClosestScopeDeclaration(IEnumerable<Declaration> declarat
615
629
return null ;
616
630
}
617
631
618
- var currentScope = matches . SingleOrDefault ( declaration => declaration . Scope == _currentScope
619
- && ! PropertyAccessors . Contains ( declaration . DeclarationType ) ) ;
620
- if ( currentScope != null )
632
+ // handle indexed property getters
633
+ var currentScopeMatches = matches . Where ( declaration =>
634
+ ( declaration . Scope == _currentScope && ! PropertyContexts . Contains ( declaration . Context . Parent . Parent . GetType ( ) ) )
635
+ || ( ( declaration . Context != null && declaration . Context . Parent . Parent is VBAParser . PropertyGetStmtContext
636
+ && _currentScopeType == DeclarationType . PropertyGet )
637
+ || ( declaration . Context != null && declaration . Context . Parent . Parent is VBAParser . PropertySetStmtContext
638
+ && _currentScopeType == DeclarationType . PropertySet )
639
+ || ( declaration . Context != null && declaration . Context . Parent . Parent is VBAParser . PropertyLetStmtContext
640
+ && _currentScopeType == DeclarationType . PropertyLet ) ) )
641
+ . ToList ( ) ;
642
+ if ( currentScopeMatches . Count == 1 )
621
643
{
622
- return currentScope ;
644
+ return currentScopeMatches [ 0 ] ;
623
645
}
624
646
625
647
// note: commented-out because it breaks the UDT member references, but property getters behave strangely still
@@ -644,6 +666,32 @@ private Declaration GetClosestScopeDeclaration(IEnumerable<Declaration> declarat
644
666
return moduleScope ;
645
667
}
646
668
669
+ var splitScope = _currentScope . Split ( '.' ) ;
670
+ if ( splitScope . Length > 2 ) // Project.Module.Procedure - i.e. if scope is deeper than module-level
671
+ {
672
+ var scope = splitScope [ 0 ] + '.' + splitScope [ 1 ] ;
673
+ var scopeMatches = matches . Where ( m => m . ParentScope == scope
674
+ && ( ! PropertyAccessors . Contains ( m . DeclarationType )
675
+ || m . DeclarationType == accessorType ) ) . ToList ( ) ;
676
+ if ( scopeMatches . Count == 1 )
677
+ {
678
+ return scopeMatches . Single ( ) ;
679
+ }
680
+
681
+ // handle standard library member shadowing:
682
+ if ( ! matches . All ( m => m . IsBuiltIn ) )
683
+ {
684
+ var ambiguousMatches = matches . Where ( m => ! m . IsBuiltIn
685
+ && ( ! PropertyAccessors . Contains ( m . DeclarationType )
686
+ || m . DeclarationType == accessorType ) ) . ToList ( ) ;
687
+
688
+ if ( ambiguousMatches . Count == 1 )
689
+ {
690
+ return ambiguousMatches . Single ( ) ;
691
+ }
692
+ }
693
+ }
694
+
647
695
var memberProcedureCallContext = context . Parent as VBAParser . ICS_B_MemberProcedureCallContext ;
648
696
if ( memberProcedureCallContext != null )
649
697
{
@@ -659,7 +707,7 @@ private Declaration GetClosestScopeDeclaration(IEnumerable<Declaration> declarat
659
707
?? Resolve ( implicitCall . iCS_S_MembersCall ( ) ) ;
660
708
}
661
709
662
- return matches . SingleOrDefault ( m => m . ParentScope == _currentScope ) ;
710
+ return null ;
663
711
}
664
712
665
713
private bool IsCurrentScopeMember ( DeclarationType accessorType , Declaration declaration )
0 commit comments