Skip to content

Commit 1c645ee

Browse files
author
Andrin Meier
committed
add tests
1 parent 19de9cd commit 1c645ee

File tree

9 files changed

+202
-60
lines changed

9 files changed

+202
-60
lines changed

Rubberduck.Parsing/Binding/SimpleNameTypeBinding.cs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ public IBoundExpression Resolve()
1919
{
2020
IBoundExpression boundExpression = null;
2121
string name = ExpressionName.GetName(_expression.name());
22-
boundExpression = ResolveEnclodingModule(name);
22+
boundExpression = ResolveEnclosingModule(name);
2323
if (boundExpression != null)
2424
{
2525
return boundExpression;
@@ -39,10 +39,11 @@ public IBoundExpression Resolve()
3939
{
4040
return boundExpression;
4141
}
42-
return ResolveModuleInReferencedProject(name);
42+
boundExpression = ResolveModuleInReferencedProject(name);
43+
return boundExpression;
4344
}
4445

45-
private IBoundExpression ResolveEnclodingModule(string name)
46+
private IBoundExpression ResolveEnclosingModule(string name)
4647
{
4748
/* Namespace tier 1:
4849
Enclosing Module namespace: A UDT or Enum type defined at the module-level in the

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -136,10 +136,10 @@ public IEnumerable<IdentifierReference> References
136136
{
137137
return _references.Union(_memberCalls);
138138
}
139-
set
140-
{
141-
_references = new ConcurrentBag<IdentifierReference>(value);
142-
}
139+
//set
140+
//{
141+
// _references = new ConcurrentBag<IdentifierReference>(value);
142+
//}
143143
}
144144

145145
private ConcurrentBag<IdentifierReference> _memberCalls = new ConcurrentBag<IdentifierReference>();

Rubberduck.Parsing/Symbols/DeclarationSymbolsListener.cs

Lines changed: 3 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,8 @@ public DeclarationSymbolsListener(
3333
IEnumerable<CommentNode> comments,
3434
IEnumerable<IAnnotation> annotations,
3535
IDictionary<Tuple<string, DeclarationType>, Attributes> attributes,
36-
HashSet<ReferencePriorityMap> projectReferences)
36+
HashSet<ReferencePriorityMap> projectReferences,
37+
Declaration projectDeclaration)
3738
{
3839
_qualifiedName = qualifiedName;
3940
_comments = comments;
@@ -44,11 +45,8 @@ public DeclarationSymbolsListener(
4445
? DeclarationType.ProceduralModule
4546
: DeclarationType.ClassModule;
4647

47-
var project = _qualifiedName.Component.Collection.Parent;
48-
var projectQualifiedName = new QualifiedModuleName(project);
4948
_projectReferences = projectReferences;
50-
51-
_projectDeclaration = CreateProjectDeclaration(projectQualifiedName, project);
49+
_projectDeclaration = projectDeclaration;
5250

5351
var key = Tuple.Create(_qualifiedName.ComponentName, declarationType);
5452
var moduleAttributes = attributes.ContainsKey(key)
@@ -70,20 +68,6 @@ public DeclarationSymbolsListener(
7068
SetCurrentScope();
7169
}
7270

73-
private Declaration CreateProjectDeclaration(QualifiedModuleName projectQualifiedName, VBProject project)
74-
{
75-
var qualifiedName = projectQualifiedName.QualifyMemberName(project.Name);
76-
var projectId = qualifiedName.QualifiedModuleName.ProjectId;
77-
var projectDeclaration = new ProjectDeclaration(qualifiedName, project.Name);
78-
var references = _projectReferences.Where(projectContainingReference => projectContainingReference.ContainsKey(projectId));
79-
foreach (var reference in references)
80-
{
81-
int priority = reference[projectId];
82-
projectDeclaration.AddProjectReference(reference.ReferencedProjectId, priority);
83-
}
84-
return projectDeclaration;
85-
}
86-
8771
private IEnumerable<IAnnotation> FindAnnotations()
8872
{
8973
if (_annotations == null)

Rubberduck.Parsing/Symbols/ReferencedDeclarationsCollector.cs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -90,18 +90,17 @@ public IEnumerable<Declaration> GetDeclarationsForReference(Reference reference)
9090
{
9191
var projectName = reference.Name;
9292
var path = reference.FullPath;
93-
var projectQualifiedModuleName = new QualifiedModuleName(projectName, path, projectName);
94-
var projectQualifiedMemberName = new QualifiedMemberName(projectQualifiedModuleName, projectName);
95-
96-
var projectDeclaration = new ProjectDeclaration(projectQualifiedMemberName, projectName);
97-
yield return projectDeclaration;
98-
9993
ITypeLib typeLibrary;
94+
// Failure to load might mean that it's a "normal" VBProject that will get parsed by us anyway.
10095
LoadTypeLibEx(path, REGKIND.REGKIND_NONE, out typeLibrary);
10196
if (typeLibrary == null)
10297
{
10398
yield break;
10499
}
100+
var projectQualifiedModuleName = new QualifiedModuleName(projectName, path, projectName);
101+
var projectQualifiedMemberName = new QualifiedMemberName(projectQualifiedModuleName, projectName);
102+
var projectDeclaration = new ProjectDeclaration(projectQualifiedMemberName, projectName);
103+
yield return projectDeclaration;
105104

106105
var typeCount = typeLibrary.GetTypeInfoCount();
107106
for (var i = 0; i < typeCount; i++)

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 30 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -165,7 +165,7 @@ private void ParseAll()
165165
}
166166
}
167167

168-
private readonly HashSet<ReferencePriorityMap> _references = new HashSet<ReferencePriorityMap>();
168+
private readonly HashSet<ReferencePriorityMap> _projectReferences = new HashSet<ReferencePriorityMap>();
169169

170170
private string GetReferenceProjectId(Reference reference, IReadOnlyList<VBProject> projects)
171171
{
@@ -197,11 +197,11 @@ private void SyncComReferences(IReadOnlyList<VBProject> projects)
197197
{
198198
var reference = vbProject.References.Item(priority);
199199
var referencedProjectId = GetReferenceProjectId(reference, projects);
200-
var map = _references.SingleOrDefault(r => r.ReferencedProjectId == referencedProjectId);
200+
var map = _projectReferences.SingleOrDefault(r => r.ReferencedProjectId == referencedProjectId);
201201
if (map == null)
202202
{
203203
map = new ReferencePriorityMap(referencedProjectId) { { projectId, priority } };
204-
_references.Add(map);
204+
_projectReferences.Add(map);
205205
}
206206
else
207207
{
@@ -221,7 +221,7 @@ private void SyncComReferences(IReadOnlyList<VBProject> projects)
221221
}
222222
}
223223

224-
var mappedIds = _references.Select(map => map.ReferencedProjectId);
224+
var mappedIds = _projectReferences.Select(map => map.ReferencedProjectId);
225225
var unmapped = projects.SelectMany(project => project.References.Cast<Reference>())
226226
.Where(reference => !mappedIds.Contains(GetReferenceProjectId(reference, projects)));
227227
foreach (var reference in unmapped)
@@ -233,7 +233,7 @@ private void SyncComReferences(IReadOnlyList<VBProject> projects)
233233
private void UnloadComReference(Reference reference, IReadOnlyList<VBProject> projects)
234234
{
235235
var referencedProjectId = GetReferenceProjectId(reference, projects);
236-
var map = _references.SingleOrDefault(r => r.ReferencedProjectId == referencedProjectId);
236+
var map = _projectReferences.SingleOrDefault(r => r.ReferencedProjectId == referencedProjectId);
237237
if (map == null || !map.IsLoaded)
238238
{
239239
// we're removing a reference we weren't tracking? ...this shouldn't happen.
@@ -243,7 +243,7 @@ private void UnloadComReference(Reference reference, IReadOnlyList<VBProject> pr
243243
map.Remove(referencedProjectId);
244244
if (!map.Any())
245245
{
246-
_references.Remove(map);
246+
_projectReferences.Remove(map);
247247
_state.RemoveBuiltInDeclarations(reference);
248248
}
249249
}
@@ -338,7 +338,7 @@ private void ResolveInternal(CancellationToken token)
338338
{
339339
return;
340340
}
341-
341+
_projectDeclarations.Clear();
342342
foreach (var kvp in _state.ParseTrees)
343343
{
344344
var qualifiedName = kvp.Key;
@@ -370,6 +370,7 @@ private void ResolveInternal(CancellationToken token)
370370
}
371371
}
372372

373+
private readonly Dictionary<string, Declaration> _projectDeclarations = new Dictionary<string, Declaration>();
373374
private void ResolveDeclarations(VBComponent component, IParseTree tree)
374375
{
375376
var qualifiedModuleName = new QualifiedModuleName(component);
@@ -392,11 +393,15 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
392393
_state.EmptyStringLiterals = emptyStringLiteralListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
393394
_state.ObsoleteLetContexts = obsoleteLetStatementListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
394395
_state.ObsoleteCallContexts = obsoleteCallStatementListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
395-
396-
// cannot locate declarations in one pass *the way it's currently implemented*,
397-
// because the context in EnterSubStmt() doesn't *yet* have child nodes when the context enters.
398-
// so we need to EnterAmbiguousIdentifier() and evaluate the parent instead - this *might* work.
399-
var declarationsListener = new DeclarationSymbolsListener(qualifiedModuleName, Accessibility.Implicit, component.Type, _state.GetModuleComments(component), _state.GetModuleAnnotations(component), _state.GetModuleAttributes(component), _references);
396+
var project = component.Collection.Parent;
397+
var projectQualifiedName = new QualifiedModuleName(project);
398+
Declaration projectDeclaration;
399+
if (!_projectDeclarations.TryGetValue(projectQualifiedName.ProjectId, out projectDeclaration))
400+
{
401+
projectDeclaration = CreateProjectDeclaration(projectQualifiedName, project);
402+
_projectDeclarations.Add(projectQualifiedName.ProjectId, projectDeclaration);
403+
}
404+
var declarationsListener = new DeclarationSymbolsListener(qualifiedModuleName, Accessibility.Implicit, component.Type, _state.GetModuleComments(component), _state.GetModuleAnnotations(component), _state.GetModuleAttributes(component), _projectReferences, projectDeclaration);
400405
// TODO: should we unify the API? consider working like the other listeners instead of event-based
401406
declarationsListener.NewDeclaration += (sender, e) => _state.AddDeclaration(e.Declaration);
402407
declarationsListener.CreateModuleDeclarations();
@@ -408,7 +413,20 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
408413
Debug.Print("Exception thrown resolving '{0}' (thread {2}): {1}", component.Name, exception, Thread.CurrentThread.ManagedThreadId);
409414
_state.SetModuleState(component, ParserState.ResolverError);
410415
}
416+
}
411417

418+
private Declaration CreateProjectDeclaration(QualifiedModuleName projectQualifiedName, VBProject project)
419+
{
420+
var qualifiedName = projectQualifiedName.QualifyMemberName(project.Name);
421+
var projectId = qualifiedName.QualifiedModuleName.ProjectId;
422+
var projectDeclaration = new ProjectDeclaration(qualifiedName, project.Name);
423+
var references = _projectReferences.Where(projectContainingReference => projectContainingReference.ContainsKey(projectId));
424+
foreach (var reference in references)
425+
{
426+
int priority = reference[projectId];
427+
projectDeclaration.AddProjectReference(reference.ReferencedProjectId, priority);
428+
}
429+
return projectDeclaration;
412430
}
413431

414432
private void ResolveReferences(DeclarationFinder finder, VBComponent component, IParseTree tree)
Lines changed: 137 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,137 @@
1+
using Microsoft.Vbe.Interop;
2+
using Microsoft.VisualStudio.TestTools.UnitTesting;
3+
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Parsing.VBA;
5+
using RubberduckTests.Mocks;
6+
using System;
7+
using System.Linq;
8+
9+
namespace RubberduckTests.Binding
10+
{
11+
[TestClass]
12+
public class SimpleNameTypeBindingTests
13+
{
14+
private const string BINDING_TARGET_NAME = "BindingTarget";
15+
private const string TEST_CLASS_NAME = "TestClass";
16+
private const string REFERENCED_PROJECT_FILEPATH = @"C:\Temp\ReferencedProjectA";
17+
18+
[TestClass]
19+
public class ResolverTests
20+
{
21+
[TestMethod]
22+
public void EnclosingModuleComesBeforeEnclosingProject()
23+
{
24+
var builder = new MockVbeBuilder();
25+
var enclosingProjectBuilder = builder.ProjectBuilder(BINDING_TARGET_NAME, vbext_ProjectProtection.vbext_pp_none);
26+
string enclosingModuleCode = "Implements " + BINDING_TARGET_NAME + Environment.NewLine + CreateEnumType(BINDING_TARGET_NAME);
27+
enclosingProjectBuilder.AddComponent(TEST_CLASS_NAME, vbext_ComponentType.vbext_ct_ClassModule, enclosingModuleCode);
28+
var enclosingProject = enclosingProjectBuilder.Build();
29+
builder.AddProject(enclosingProject);
30+
var vbe = builder.Build();
31+
var state = Parse(vbe);
32+
33+
var declaration = state.AllUserDeclarations.Single(d => d.DeclarationType == DeclarationType.Enumeration && d.IdentifierName == BINDING_TARGET_NAME);
34+
35+
Assert.AreEqual(1, declaration.References.Count());
36+
}
37+
38+
[TestMethod]
39+
public void EnclosingProjectComesBeforeOtherModuleInEnclosingProject()
40+
{
41+
var builder = new MockVbeBuilder();
42+
var enclosingProjectBuilder = builder.ProjectBuilder(BINDING_TARGET_NAME, vbext_ProjectProtection.vbext_pp_none);
43+
enclosingProjectBuilder.AddComponent(TEST_CLASS_NAME, vbext_ComponentType.vbext_ct_ClassModule, "Implements " + BINDING_TARGET_NAME);
44+
enclosingProjectBuilder.AddComponent("AnyModule", vbext_ComponentType.vbext_ct_StdModule, CreateEnumType(BINDING_TARGET_NAME));
45+
var enclosingProject = enclosingProjectBuilder.Build();
46+
builder.AddProject(enclosingProject);
47+
var vbe = builder.Build();
48+
var state = Parse(vbe);
49+
50+
var declaration = state.AllUserDeclarations.Single(d => d.DeclarationType == DeclarationType.Project && d.IdentifierName == BINDING_TARGET_NAME);
51+
52+
Assert.AreEqual(1, declaration.References.Count());
53+
}
54+
55+
[TestMethod]
56+
public void OtherModuleInEnclosingProjectComesBeforeReferencedProjectModule()
57+
{
58+
var builder = new MockVbeBuilder();
59+
const string REFERENCED_PROJECT_NAME = "AnyReferencedProjectName";
60+
61+
var referencedProjectBuilder = builder.ProjectBuilder(REFERENCED_PROJECT_NAME, REFERENCED_PROJECT_FILEPATH, vbext_ProjectProtection.vbext_pp_none);
62+
referencedProjectBuilder.AddComponent(BINDING_TARGET_NAME, vbext_ComponentType.vbext_ct_ClassModule, string.Empty);
63+
var referencedProject = referencedProjectBuilder.Build();
64+
builder.AddProject(referencedProject);
65+
66+
var enclosingProjectBuilder = builder.ProjectBuilder("AnyProjectName", vbext_ProjectProtection.vbext_pp_none);
67+
enclosingProjectBuilder.AddReference(REFERENCED_PROJECT_NAME, REFERENCED_PROJECT_FILEPATH);
68+
enclosingProjectBuilder.AddComponent(TEST_CLASS_NAME, vbext_ComponentType.vbext_ct_ClassModule, "Implements " + BINDING_TARGET_NAME);
69+
enclosingProjectBuilder.AddComponent("AnyModule", vbext_ComponentType.vbext_ct_StdModule, CreateEnumType(BINDING_TARGET_NAME));
70+
var enclosingProject = enclosingProjectBuilder.Build();
71+
builder.AddProject(enclosingProject);
72+
73+
var vbe = builder.Build();
74+
var state = Parse(vbe);
75+
76+
var declaration = state.AllUserDeclarations.Single(d => d.DeclarationType == DeclarationType.Enumeration && d.IdentifierName == BINDING_TARGET_NAME);
77+
78+
Assert.AreEqual(1, declaration.References.Count());
79+
}
80+
81+
[TestMethod]
82+
public void ReferencedProjectModuleComesBeforeReferencedProjectType()
83+
{
84+
var builder = new MockVbeBuilder();
85+
const string REFERENCED_PROJECT_NAME = "AnyReferencedProjectName";
86+
87+
var referencedProjectBuilder = builder.ProjectBuilder(REFERENCED_PROJECT_NAME, REFERENCED_PROJECT_FILEPATH, vbext_ProjectProtection.vbext_pp_none);
88+
referencedProjectBuilder.AddComponent(BINDING_TARGET_NAME, vbext_ComponentType.vbext_ct_StdModule, CreateEnumType(BINDING_TARGET_NAME));
89+
var referencedProject = referencedProjectBuilder.Build();
90+
builder.AddProject(referencedProject);
91+
92+
var enclosingProjectBuilder = builder.ProjectBuilder("AnyProjectName", vbext_ProjectProtection.vbext_pp_none);
93+
enclosingProjectBuilder.AddReference(REFERENCED_PROJECT_NAME, REFERENCED_PROJECT_FILEPATH);
94+
enclosingProjectBuilder.AddComponent(TEST_CLASS_NAME, vbext_ComponentType.vbext_ct_ClassModule, "Implements " + BINDING_TARGET_NAME);
95+
var enclosingProject = enclosingProjectBuilder.Build();
96+
builder.AddProject(enclosingProject);
97+
98+
var vbe = builder.Build();
99+
var state = Parse(vbe);
100+
101+
var declaration = state.AllUserDeclarations.Single(d => d.DeclarationType == DeclarationType.ProceduralModule && d.IdentifierName == BINDING_TARGET_NAME);
102+
103+
Assert.AreEqual(1, declaration.References.Count());
104+
}
105+
106+
private static RubberduckParserState Parse(Moq.Mock<VBE> vbe)
107+
{
108+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState());
109+
parser.Parse();
110+
if (parser.State.Status != ParserState.Ready)
111+
{
112+
Assert.Inconclusive("Parser state should be 'Ready', but returns '{0}'.", parser.State.Status);
113+
}
114+
var state = parser.State;
115+
return state;
116+
}
117+
118+
private string CreateEnumType(string typeName)
119+
{
120+
return string.Format(@"
121+
Public Enum {0}
122+
TestEnumMember
123+
End Enum
124+
", typeName);
125+
}
126+
127+
private string CreateUdt(string typeName)
128+
{
129+
return string.Format(@"
130+
Public Type {0}
131+
TestTypeMember As String
132+
End Type
133+
", typeName);
134+
}
135+
}
136+
}
137+
}

0 commit comments

Comments
 (0)