@@ -51,27 +51,27 @@ public IdentifierReferenceResolver(QualifiedModuleName qualifiedModuleName, Decl
51
51
52
52
_moduleTypes = new [ ]
53
53
{
54
- DeclarationType . ProceduralModule ,
54
+ DeclarationType . ProceduralModule ,
55
55
DeclarationType . ClassModule ,
56
56
} ;
57
57
58
58
_memberTypes = new [ ]
59
59
{
60
- DeclarationType . Procedure ,
61
- DeclarationType . Function ,
62
- DeclarationType . PropertyGet ,
63
- DeclarationType . PropertyLet ,
64
- DeclarationType . PropertySet ,
60
+ DeclarationType . Procedure ,
61
+ DeclarationType . Function ,
62
+ DeclarationType . PropertyGet ,
63
+ DeclarationType . PropertyLet ,
64
+ DeclarationType . PropertySet ,
65
65
} ;
66
66
67
67
_returningMemberTypes = new [ ]
68
68
{
69
69
DeclarationType . Function ,
70
- DeclarationType . PropertyGet ,
70
+ DeclarationType . PropertyGet ,
71
71
} ;
72
72
73
73
_moduleDeclaration = finder . MatchName ( _qualifiedModuleName . ComponentName )
74
- . SingleOrDefault ( item =>
74
+ . SingleOrDefault ( item =>
75
75
( item . DeclarationType == DeclarationType . ClassModule || item . DeclarationType == DeclarationType . ProceduralModule )
76
76
&& item . QualifiedName . QualifiedModuleName . Equals ( _qualifiedModuleName ) ) ;
77
77
@@ -91,10 +91,10 @@ public void SetCurrentScope()
91
91
public void SetCurrentScope ( string memberName , DeclarationType type )
92
92
{
93
93
Debug . WriteLine ( "Setting current scope: {0} ({1}) in thread {2}" , memberName , type , Thread . CurrentThread . ManagedThreadId ) ;
94
-
95
- _currentParent = _declarationFinder . MatchName ( memberName ) . SingleOrDefault ( item =>
94
+
95
+ _currentParent = _declarationFinder . MatchName ( memberName ) . SingleOrDefault ( item =>
96
96
item . QualifiedName . QualifiedModuleName == _qualifiedModuleName && item . DeclarationType == type ) ;
97
-
97
+
98
98
_currentScope = _declarationFinder . MatchName ( memberName ) . SingleOrDefault ( item =>
99
99
item . QualifiedName . QualifiedModuleName == _qualifiedModuleName && item . DeclarationType == type ) ?? _moduleDeclaration ;
100
100
@@ -175,7 +175,7 @@ private IEnumerable<IAnnotation> FindAnnotations(int line)
175
175
private void ResolveType ( VBAParser . ICS_S_MembersCallContext context )
176
176
{
177
177
var first = context . iCS_S_VariableOrProcedureCall ( ) . ambiguousIdentifier ( ) ;
178
- var identifiers = new [ ] { first } . Concat ( context . iCS_S_MemberCall ( )
178
+ var identifiers = new [ ] { first } . Concat ( context . iCS_S_MemberCall ( )
179
179
. Select ( member => member . iCS_S_VariableOrProcedureCall ( ) . ambiguousIdentifier ( ) ) )
180
180
. ToList ( ) ;
181
181
ResolveType ( identifiers ) ;
@@ -310,7 +310,7 @@ private Declaration ResolveType(IList<VBAParser.AmbiguousIdentifierContext> iden
310
310
// if there are 3 identifiers, type isn't in current project.
311
311
if ( identifiers . Count != 3 )
312
312
{
313
-
313
+
314
314
var moduleMatch = _declarationFinder . FindStdModule ( projectMatch , identifiers [ 0 ] . GetText ( ) ) ;
315
315
if ( moduleMatch != null )
316
316
{
@@ -369,15 +369,15 @@ private Declaration ResolveInScopeType(string identifier, Declaration scope)
369
369
{
370
370
return sameScopeUdt . Single ( ) ;
371
371
}
372
-
372
+
373
373
// todo: try to resolve identifier using referenced projects
374
374
375
375
return null ;
376
376
}
377
-
377
+
378
378
private Declaration ResolveType ( Declaration parent )
379
379
{
380
- if ( parent != null && ( parent . DeclarationType == DeclarationType . UserDefinedType
380
+ if ( parent != null && ( parent . DeclarationType == DeclarationType . UserDefinedType
381
381
|| parent . DeclarationType == DeclarationType . Enumeration
382
382
|| parent . DeclarationType == DeclarationType . Project
383
383
|| parent . DeclarationType == DeclarationType . ProceduralModule
@@ -415,7 +415,7 @@ private Declaration ResolveType(Declaration parent)
415
415
result = matches . Where ( item =>
416
416
_moduleTypes . Contains ( item . DeclarationType )
417
417
&& item . ProjectId == _currentScope . ProjectId )
418
- . ToList ( ) ;
418
+ . ToList ( ) ;
419
419
}
420
420
421
421
if ( ! result . Any ( ) )
@@ -425,7 +425,7 @@ private Declaration ResolveType(Declaration parent)
425
425
. ToList ( ) ;
426
426
}
427
427
428
- return result . Count == 1 ? result . SingleOrDefault ( ) :
428
+ return result . Count == 1 ? result . SingleOrDefault ( ) :
429
429
matches . Count == 1 ? matches . First ( ) : null ;
430
430
}
431
431
@@ -527,6 +527,10 @@ private Declaration ResolveInternal(VBAParser.ICS_S_VariableOrProcedureCallConte
527
527
{
528
528
return null ;
529
529
}
530
+ if ( ComesFromImplementsStmt ( context ) )
531
+ {
532
+ return null ;
533
+ }
530
534
531
535
var identifierContext = context . ambiguousIdentifier ( ) ;
532
536
var fieldCall = context . dictionaryCallStmt ( ) ;
@@ -545,6 +549,19 @@ private Declaration ResolveInternal(VBAParser.ICS_S_VariableOrProcedureCallConte
545
549
return result ;
546
550
}
547
551
552
+ private bool ComesFromImplementsStmt ( RuleContext context )
553
+ {
554
+ if ( context == null )
555
+ {
556
+ return false ;
557
+ }
558
+ if ( context . Parent is VBAParser . ImplementsStmtContext )
559
+ {
560
+ return true ;
561
+ }
562
+ return ComesFromImplementsStmt ( context . Parent ) ;
563
+ }
564
+
548
565
private Declaration ResolveInternal ( VBAParser . DictionaryCallStmtContext fieldCall , Declaration parent , bool hasExplicitLetStatement = false , bool isAssignmentTarget = false )
549
566
{
550
567
if ( fieldCall == null )
@@ -632,7 +649,7 @@ private Declaration ResolveInternal(VBAParser.ICS_S_MembersCallContext context,
632
649
// if we're on the left side of an assignment, only the last memberCall is the assignment target.
633
650
var isLast = memberCall . Equals ( lastCall ) ;
634
651
var accessor = isLast
635
- ? accessorType
652
+ ? accessorType
636
653
: ContextAccessorType . GetValueOrReference ;
637
654
var isTarget = isLast && isAssignmentTarget ;
638
655
@@ -744,7 +761,7 @@ public void Resolve(VBAParser.ICS_B_MemberProcedureCallContext context)
744
761
member . AddReference ( reference ) ;
745
762
_alreadyResolved . Add ( reference . Context ) ;
746
763
}
747
-
764
+
748
765
var fieldCall = context . dictionaryCallStmt ( ) ;
749
766
ResolveInternal ( fieldCall , member ) ;
750
767
}
@@ -803,7 +820,7 @@ public void Resolve(VBAParser.ICS_S_MembersCallContext context)
803
820
804
821
if ( parent == null )
805
822
{
806
-
823
+
807
824
808
825
return ;
809
826
}
@@ -981,7 +998,7 @@ public void Resolve(VBAParser.ImplementsStmtContext context)
981
998
var boundExpression = _bindingService . Resolve ( _moduleDeclaration , _currentScope , context . valueStmt ( ) . GetText ( ) ) ;
982
999
if ( boundExpression != null )
983
1000
{
984
- _boundExpressionVisitor . AddIdentifierReferences ( boundExpression , declaration => CreateReference ( context . valueStmt ( ) , declaration ) ) ;
1001
+ _boundExpressionVisitor . AddIdentifierReferences ( boundExpression , declaration => CreateReference ( context . valueStmt ( ) , declaration ) ) ;
985
1002
}
986
1003
}
987
1004
@@ -1031,7 +1048,7 @@ private Declaration FindFunctionOrPropertyGetter(string identifierName, Declarat
1031
1048
return parent ;
1032
1049
}
1033
1050
1034
- private Declaration FindLocalScopeDeclaration ( string identifierName , Declaration localScope = null , bool parentContextIsVariableOrProcedureCall = false , bool isAssignmentTarget = false )
1051
+ private Declaration FindLocalScopeDeclaration ( string identifierName , Declaration localScope = null , bool parentContextIsVariableOrProcedureCall = false , bool isAssignmentTarget = false )
1035
1052
{
1036
1053
if ( localScope == null )
1037
1054
{
@@ -1048,7 +1065,7 @@ private Declaration FindLocalScopeDeclaration(string identifierName, Declaration
1048
1065
1049
1066
var results = matches . Where ( item =>
1050
1067
( ( localScope . Equals ( item . ParentDeclaration )
1051
- || ( item . DeclarationType == DeclarationType . Parameter && localScope . Equals ( item . ParentScopeDeclaration ) ) )
1068
+ || ( item . DeclarationType == DeclarationType . Parameter && localScope . Equals ( item . ParentScopeDeclaration ) ) )
1052
1069
|| ( isAssignmentTarget && item . Scope == localScope . Scope ) )
1053
1070
&& localScope . Context . GetSelection ( ) . Contains ( item . Selection )
1054
1071
&& ! _moduleTypes . Contains ( item . DeclarationType ) )
@@ -1106,7 +1123,7 @@ private Declaration FindModuleScopeDeclaration(string identifierName, Declaratio
1106
1123
1107
1124
if ( matches . Any ( ) && ! result . Any ( ) )
1108
1125
{
1109
- result = matches . Where ( item =>
1126
+ result = matches . Where ( item =>
1110
1127
( localScope != null && localScope . Equals ( item . ParentScopeDeclaration ) )
1111
1128
&& ! item . DeclarationType . HasFlag ( DeclarationType . Member )
1112
1129
&& ! _moduleTypes . Contains ( item . DeclarationType )
@@ -1187,7 +1204,7 @@ private bool IsStaticClass(Declaration declaration)
1187
1204
1188
1205
private Declaration FindProjectScopeDeclaration ( string identifierName , Declaration localScope = null , ContextAccessorType accessorType = ContextAccessorType . GetValueOrReference , bool hasStringQualifier = false )
1189
1206
{
1190
- var matches = _declarationFinder . MatchName ( identifierName ) . Where ( item =>
1207
+ var matches = _declarationFinder . MatchName ( identifierName ) . Where ( item =>
1191
1208
item . DeclarationType == DeclarationType . Project
1192
1209
|| item . DeclarationType == DeclarationType . ProceduralModule
1193
1210
|| IsStaticClass ( item )
@@ -1227,7 +1244,7 @@ private Declaration FindProjectScopeDeclaration(string identifierName, Declarati
1227
1244
{
1228
1245
if ( localScope == null )
1229
1246
{
1230
- var names = new [ ] { "Global" , "_Global" } ;
1247
+ var names = new [ ] { "Global" , "_Global" } ;
1231
1248
var appGlobals = temp . Where ( item => names . Contains ( item . ParentDeclaration . IdentifierName ) ) . ToList ( ) ;
1232
1249
if ( appGlobals . Count == 1 )
1233
1250
{
@@ -1276,7 +1293,7 @@ private static bool IsPublicOrGlobal(Declaration item)
1276
1293
1277
1294
private bool IsUserDeclarationInProjectScope ( Declaration item )
1278
1295
{
1279
- var isNonMemberUserDeclaration = ! item . IsBuiltIn
1296
+ var isNonMemberUserDeclaration = ! item . IsBuiltIn
1280
1297
&& ! item . DeclarationType . HasFlag ( DeclarationType . Member )
1281
1298
// events can't be called outside the class they're declared in, exclude them as well:
1282
1299
&& item . DeclarationType != DeclarationType . Event ;
@@ -1288,15 +1305,15 @@ private bool IsUserDeclarationInProjectScope(Declaration item)
1288
1305
private static bool IsBuiltInDeclarationInScope ( Declaration item , Declaration localScope )
1289
1306
{
1290
1307
var isBuiltInNonEvent = item . IsBuiltIn && item . DeclarationType != DeclarationType . Event ;
1291
-
1308
+
1292
1309
// if localScope is null, we can only resolve to a global:
1293
1310
// note: built-in declarations are designed that way
1294
1311
var isBuiltInGlobal = localScope == null && item . Accessibility == Accessibility . Global ;
1295
1312
1296
1313
// if localScope is not null, we can resolve to any public or global in that scope:
1297
1314
var isInLocalScope = ( localScope != null && item . Accessibility == Accessibility . Global
1298
1315
&& localScope . IdentifierName == item . ParentDeclaration . IdentifierName )
1299
- || ( localScope != null && localScope . QualifiedName . QualifiedModuleName . Component != null
1316
+ || ( localScope != null && localScope . QualifiedName . QualifiedModuleName . Component != null
1300
1317
&& localScope . QualifiedName . QualifiedModuleName . Component . Type == Microsoft . Vbe . Interop . vbext_ComponentType . vbext_ct_Document
1301
1318
&& item . Accessibility == Accessibility . Public && item . ParentDeclaration . DeclarationType == localScope . DeclarationType ) ;
1302
1319
0 commit comments