Skip to content

Commit 8a68ad4

Browse files
author
Andrin Meier
committed
add tests
1 parent 8f64c9b commit 8a68ad4

9 files changed

+272
-36
lines changed

Rubberduck.Parsing/Binding/MemberAccessTypeBinding.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -152,7 +152,7 @@ procedural module.
152152
}
153153
else
154154
{
155-
var proceduralModuleInReferencedProject = _declarationFinder.FindModuleReferencedProject(_project, referencedProject, _module, name, DeclarationType.ClassModule);
155+
var proceduralModuleInReferencedProject = _declarationFinder.FindModuleReferencedProject(_project, _module, referencedProject, name, DeclarationType.ProceduralModule);
156156
if (proceduralModuleInReferencedProject != null)
157157
{
158158
return new MemberAccessExpression(proceduralModuleInReferencedProject, ExpressionClassification.ProceduralModule, GetExpressionContext(), lExpression);

Rubberduck.Parsing/Binding/SimpleNameTypeBinding.cs

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -83,13 +83,21 @@ procedural module or class module contained in the enclosing project.
8383
var referencedProject = _declarationFinder.FindReferencedProject(_project, name);
8484
if (referencedProject != null)
8585
{
86-
return new SimpleNameExpression(referencedProject, ExpressionClassification.Type, _expression);
86+
return new SimpleNameExpression(referencedProject, ExpressionClassification.Project, _expression);
87+
}
88+
if (_module.DeclarationType == DeclarationType.ProceduralModule && _module.IdentifierName == name)
89+
{
90+
return new SimpleNameExpression(_module, ExpressionClassification.ProceduralModule, _expression);
8791
}
8892
var proceduralModuleEnclosingProject = _declarationFinder.FindModuleEnclosingProjectWithoutEnclosingModule(_project, _module, name, DeclarationType.ProceduralModule);
8993
if (proceduralModuleEnclosingProject != null)
9094
{
9195
return new SimpleNameExpression(proceduralModuleEnclosingProject, ExpressionClassification.ProceduralModule, _expression);
9296
}
97+
if (_module.DeclarationType == DeclarationType.ClassModule && _module.IdentifierName == name)
98+
{
99+
return new SimpleNameExpression(_module, ExpressionClassification.Type, _expression);
100+
}
93101
var classEnclosingProject = _declarationFinder.FindModuleEnclosingProjectWithoutEnclosingModule(_project, _module, name, DeclarationType.ClassModule);
94102
if (classEnclosingProject != null)
95103
{

Rubberduck.Parsing/Symbols/ClassModuleDeclaration.cs

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -8,13 +8,16 @@ namespace Rubberduck.Parsing.Symbols
88
{
99
public sealed class ClassModuleDeclaration : Declaration
1010
{
11+
private readonly bool _isExposed;
12+
1113
public ClassModuleDeclaration(
1214
QualifiedMemberName qualifiedName,
1315
Declaration projectDeclaration,
1416
string name,
1517
bool isBuiltIn,
1618
IEnumerable<IAnnotation> annotations,
17-
Attributes attributes)
19+
Attributes attributes,
20+
bool isExposed = false)
1821
: base(
1922
qualifiedName,
2023
projectDeclaration,
@@ -30,6 +33,7 @@ public ClassModuleDeclaration(
3033
annotations,
3134
attributes)
3235
{
36+
_isExposed = isExposed;
3337
}
3438

3539
/// <summary>
@@ -40,12 +44,13 @@ public bool IsExposed
4044
{
4145
get
4246
{
47+
bool attributeIsExposed = false;
4348
IEnumerable<string> value;
4449
if (Attributes.TryGetValue("VB_Exposed", out value))
4550
{
46-
return value.Single() == "True";
51+
attributeIsExposed = value.Single() == "True";
4752
}
48-
return false;
53+
return _isExposed || attributeIsExposed;
4954
}
5055
}
5156
}

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -106,6 +106,10 @@ public Declaration(
106106

107107
public static Declaration GetMemberModule(Declaration member)
108108
{
109+
if (member.ParentDeclaration == null)
110+
{
111+
return null;
112+
}
109113
if (member.ParentDeclaration.DeclarationType == DeclarationType.ClassModule || member.ParentDeclaration.DeclarationType == DeclarationType.ProceduralModule)
110114
{
111115
return member.ParentDeclaration;
@@ -115,6 +119,10 @@ public static Declaration GetMemberModule(Declaration member)
115119

116120
public static Declaration GetMemberProject(Declaration declaration)
117121
{
122+
if (declaration.ParentDeclaration == null)
123+
{
124+
return null;
125+
}
118126
if (declaration.ParentDeclaration.DeclarationType == DeclarationType.Project)
119127
{
120128
return declaration.ParentDeclaration;

Rubberduck.Parsing/Symbols/IdentifierReferenceListener.cs

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
using Antlr4.Runtime;
12
using Rubberduck.Parsing.Grammar;
23

34
namespace Rubberduck.Parsing.Symbols
@@ -130,9 +131,28 @@ public override void EnterICS_S_ProcedureOrArrayCall(VBAParser.ICS_S_ProcedureOr
130131

131132
public override void EnterICS_S_MembersCall(VBAParser.ICS_S_MembersCallContext context)
132133
{
134+
// Implement statements are handled separately and directly through new binding expressions.
135+
// Prevent duplicate references.
136+
if (ComesFromImplementsStmt(context))
137+
{
138+
return;
139+
}
133140
_resolver.Resolve(context);
134141
}
135142

143+
private bool ComesFromImplementsStmt(RuleContext context)
144+
{
145+
if (context == null)
146+
{
147+
return false;
148+
}
149+
if (context.Parent is VBAParser.ImplementsStmtContext)
150+
{
151+
return true;
152+
}
153+
return ComesFromImplementsStmt(context.Parent);
154+
}
155+
136156
public override void EnterICS_S_DictionaryCall(VBAParser.ICS_S_DictionaryCallContext context)
137157
{
138158
if (context.Parent.GetType() != typeof(VBAParser.ICS_S_MemberCallContext))

Rubberduck.Parsing/Symbols/IdentifierReferenceResolver.cs

Lines changed: 47 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -51,27 +51,27 @@ public IdentifierReferenceResolver(QualifiedModuleName qualifiedModuleName, Decl
5151

5252
_moduleTypes = new[]
5353
{
54-
DeclarationType.ProceduralModule,
54+
DeclarationType.ProceduralModule,
5555
DeclarationType.ClassModule,
5656
};
5757

5858
_memberTypes = new[]
5959
{
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,
6565
};
6666

6767
_returningMemberTypes = new[]
6868
{
6969
DeclarationType.Function,
70-
DeclarationType.PropertyGet,
70+
DeclarationType.PropertyGet,
7171
};
7272

7373
_moduleDeclaration = finder.MatchName(_qualifiedModuleName.ComponentName)
74-
.SingleOrDefault(item =>
74+
.SingleOrDefault(item =>
7575
(item.DeclarationType == DeclarationType.ClassModule || item.DeclarationType == DeclarationType.ProceduralModule)
7676
&& item.QualifiedName.QualifiedModuleName.Equals(_qualifiedModuleName));
7777

@@ -91,10 +91,10 @@ public void SetCurrentScope()
9191
public void SetCurrentScope(string memberName, DeclarationType type)
9292
{
9393
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 =>
9696
item.QualifiedName.QualifiedModuleName == _qualifiedModuleName && item.DeclarationType == type);
97-
97+
9898
_currentScope = _declarationFinder.MatchName(memberName).SingleOrDefault(item =>
9999
item.QualifiedName.QualifiedModuleName == _qualifiedModuleName && item.DeclarationType == type) ?? _moduleDeclaration;
100100

@@ -175,7 +175,7 @@ private IEnumerable<IAnnotation> FindAnnotations(int line)
175175
private void ResolveType(VBAParser.ICS_S_MembersCallContext context)
176176
{
177177
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()
179179
.Select(member => member.iCS_S_VariableOrProcedureCall().ambiguousIdentifier()))
180180
.ToList();
181181
ResolveType(identifiers);
@@ -310,7 +310,7 @@ private Declaration ResolveType(IList<VBAParser.AmbiguousIdentifierContext> iden
310310
// if there are 3 identifiers, type isn't in current project.
311311
if (identifiers.Count != 3)
312312
{
313-
313+
314314
var moduleMatch = _declarationFinder.FindStdModule(projectMatch, identifiers[0].GetText());
315315
if (moduleMatch != null)
316316
{
@@ -369,15 +369,15 @@ private Declaration ResolveInScopeType(string identifier, Declaration scope)
369369
{
370370
return sameScopeUdt.Single();
371371
}
372-
372+
373373
// todo: try to resolve identifier using referenced projects
374374

375375
return null;
376376
}
377-
377+
378378
private Declaration ResolveType(Declaration parent)
379379
{
380-
if (parent != null && (parent.DeclarationType == DeclarationType.UserDefinedType
380+
if (parent != null && (parent.DeclarationType == DeclarationType.UserDefinedType
381381
|| parent.DeclarationType == DeclarationType.Enumeration
382382
|| parent.DeclarationType == DeclarationType.Project
383383
|| parent.DeclarationType == DeclarationType.ProceduralModule
@@ -415,7 +415,7 @@ private Declaration ResolveType(Declaration parent)
415415
result = matches.Where(item =>
416416
_moduleTypes.Contains(item.DeclarationType)
417417
&& item.ProjectId == _currentScope.ProjectId)
418-
.ToList();
418+
.ToList();
419419
}
420420

421421
if (!result.Any())
@@ -425,7 +425,7 @@ private Declaration ResolveType(Declaration parent)
425425
.ToList();
426426
}
427427

428-
return result.Count == 1 ? result.SingleOrDefault() :
428+
return result.Count == 1 ? result.SingleOrDefault() :
429429
matches.Count == 1 ? matches.First() : null;
430430
}
431431

@@ -527,6 +527,10 @@ private Declaration ResolveInternal(VBAParser.ICS_S_VariableOrProcedureCallConte
527527
{
528528
return null;
529529
}
530+
if (ComesFromImplementsStmt(context))
531+
{
532+
return null;
533+
}
530534

531535
var identifierContext = context.ambiguousIdentifier();
532536
var fieldCall = context.dictionaryCallStmt();
@@ -545,6 +549,19 @@ private Declaration ResolveInternal(VBAParser.ICS_S_VariableOrProcedureCallConte
545549
return result;
546550
}
547551

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+
548565
private Declaration ResolveInternal(VBAParser.DictionaryCallStmtContext fieldCall, Declaration parent, bool hasExplicitLetStatement = false, bool isAssignmentTarget = false)
549566
{
550567
if (fieldCall == null)
@@ -632,7 +649,7 @@ private Declaration ResolveInternal(VBAParser.ICS_S_MembersCallContext context,
632649
// if we're on the left side of an assignment, only the last memberCall is the assignment target.
633650
var isLast = memberCall.Equals(lastCall);
634651
var accessor = isLast
635-
? accessorType
652+
? accessorType
636653
: ContextAccessorType.GetValueOrReference;
637654
var isTarget = isLast && isAssignmentTarget;
638655

@@ -744,7 +761,7 @@ public void Resolve(VBAParser.ICS_B_MemberProcedureCallContext context)
744761
member.AddReference(reference);
745762
_alreadyResolved.Add(reference.Context);
746763
}
747-
764+
748765
var fieldCall = context.dictionaryCallStmt();
749766
ResolveInternal(fieldCall, member);
750767
}
@@ -803,7 +820,7 @@ public void Resolve(VBAParser.ICS_S_MembersCallContext context)
803820

804821
if (parent == null)
805822
{
806-
823+
807824

808825
return;
809826
}
@@ -981,7 +998,7 @@ public void Resolve(VBAParser.ImplementsStmtContext context)
981998
var boundExpression = _bindingService.Resolve(_moduleDeclaration, _currentScope, context.valueStmt().GetText());
982999
if (boundExpression != null)
9831000
{
984-
_boundExpressionVisitor.AddIdentifierReferences(boundExpression, declaration => CreateReference(context.valueStmt(), declaration));
1001+
_boundExpressionVisitor.AddIdentifierReferences(boundExpression, declaration => CreateReference(context.valueStmt(), declaration));
9851002
}
9861003
}
9871004

@@ -1031,7 +1048,7 @@ private Declaration FindFunctionOrPropertyGetter(string identifierName, Declarat
10311048
return parent;
10321049
}
10331050

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)
10351052
{
10361053
if (localScope == null)
10371054
{
@@ -1048,7 +1065,7 @@ private Declaration FindLocalScopeDeclaration(string identifierName, Declaration
10481065

10491066
var results = matches.Where(item =>
10501067
((localScope.Equals(item.ParentDeclaration)
1051-
|| (item.DeclarationType == DeclarationType.Parameter && localScope.Equals(item.ParentScopeDeclaration)))
1068+
|| (item.DeclarationType == DeclarationType.Parameter && localScope.Equals(item.ParentScopeDeclaration)))
10521069
|| (isAssignmentTarget && item.Scope == localScope.Scope))
10531070
&& localScope.Context.GetSelection().Contains(item.Selection)
10541071
&& !_moduleTypes.Contains(item.DeclarationType))
@@ -1106,7 +1123,7 @@ private Declaration FindModuleScopeDeclaration(string identifierName, Declaratio
11061123

11071124
if (matches.Any() && !result.Any())
11081125
{
1109-
result = matches.Where(item =>
1126+
result = matches.Where(item =>
11101127
(localScope != null && localScope.Equals(item.ParentScopeDeclaration))
11111128
&& !item.DeclarationType.HasFlag(DeclarationType.Member)
11121129
&& !_moduleTypes.Contains(item.DeclarationType)
@@ -1187,7 +1204,7 @@ private bool IsStaticClass(Declaration declaration)
11871204

11881205
private Declaration FindProjectScopeDeclaration(string identifierName, Declaration localScope = null, ContextAccessorType accessorType = ContextAccessorType.GetValueOrReference, bool hasStringQualifier = false)
11891206
{
1190-
var matches = _declarationFinder.MatchName(identifierName).Where(item =>
1207+
var matches = _declarationFinder.MatchName(identifierName).Where(item =>
11911208
item.DeclarationType == DeclarationType.Project
11921209
|| item.DeclarationType == DeclarationType.ProceduralModule
11931210
|| IsStaticClass(item)
@@ -1227,7 +1244,7 @@ private Declaration FindProjectScopeDeclaration(string identifierName, Declarati
12271244
{
12281245
if (localScope == null)
12291246
{
1230-
var names = new[] {"Global", "_Global"};
1247+
var names = new[] { "Global", "_Global" };
12311248
var appGlobals = temp.Where(item => names.Contains(item.ParentDeclaration.IdentifierName)).ToList();
12321249
if (appGlobals.Count == 1)
12331250
{
@@ -1276,7 +1293,7 @@ private static bool IsPublicOrGlobal(Declaration item)
12761293

12771294
private bool IsUserDeclarationInProjectScope(Declaration item)
12781295
{
1279-
var isNonMemberUserDeclaration = !item.IsBuiltIn
1296+
var isNonMemberUserDeclaration = !item.IsBuiltIn
12801297
&& !item.DeclarationType.HasFlag(DeclarationType.Member)
12811298
// events can't be called outside the class they're declared in, exclude them as well:
12821299
&& item.DeclarationType != DeclarationType.Event;
@@ -1288,15 +1305,15 @@ private bool IsUserDeclarationInProjectScope(Declaration item)
12881305
private static bool IsBuiltInDeclarationInScope(Declaration item, Declaration localScope)
12891306
{
12901307
var isBuiltInNonEvent = item.IsBuiltIn && item.DeclarationType != DeclarationType.Event;
1291-
1308+
12921309
// if localScope is null, we can only resolve to a global:
12931310
// note: built-in declarations are designed that way
12941311
var isBuiltInGlobal = localScope == null && item.Accessibility == Accessibility.Global;
12951312

12961313
// if localScope is not null, we can resolve to any public or global in that scope:
12971314
var isInLocalScope = (localScope != null && item.Accessibility == Accessibility.Global
12981315
&& localScope.IdentifierName == item.ParentDeclaration.IdentifierName)
1299-
|| (localScope != null && localScope.QualifiedName.QualifiedModuleName.Component != null
1316+
|| (localScope != null && localScope.QualifiedName.QualifiedModuleName.Component != null
13001317
&& localScope.QualifiedName.QualifiedModuleName.Component.Type == Microsoft.Vbe.Interop.vbext_ComponentType.vbext_ct_Document
13011318
&& item.Accessibility == Accessibility.Public && item.ParentDeclaration.DeclarationType == localScope.DeclarationType);
13021319

Rubberduck.Parsing/Symbols/ReferencedDeclarationsCollector.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -156,7 +156,7 @@ public IEnumerable<Declaration> GetDeclarationsForReference(Reference reference)
156156
}
157157
else
158158
{
159-
moduleDeclaration = new ClassModuleDeclaration(typeQualifiedMemberName, projectDeclaration, typeName, true, new List<IAnnotation>(), attributes);
159+
moduleDeclaration = new ClassModuleDeclaration(typeQualifiedMemberName, projectDeclaration, typeName, true, new List<IAnnotation>(), attributes, isExposed: true);
160160
}
161161
yield return moduleDeclaration;
162162

0 commit comments

Comments
 (0)