Skip to content

Commit e2f75e8

Browse files
committed
Merge pull request #1351 from autoboosh/declarationhierarchy
associate project references correctly and in the correct order (#1340, #1347)
2 parents ee0fdab + 729d09c commit e2f75e8

File tree

11 files changed

+146
-79
lines changed

11 files changed

+146
-79
lines changed

RetailCoder.VBE/UI/Command/Refactorings/RefactorExtractInterfaceCommand.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ public override bool CanExecute(object parameter)
4444
item.QualifiedName.QualifiedModuleName.Equals(selection.QualifiedName)
4545
&& item.IdentifierName == selection.QualifiedName.ComponentName
4646
&& (item.DeclarationType == DeclarationType.Class || item.DeclarationType == DeclarationType.Document || item.DeclarationType == DeclarationType.UserForm));
47-
var hasMembers = _state.AllUserDeclarations.Any(item => item.DeclarationType.HasFlag(DeclarationType.Member) && item.ParentDeclaration.Equals(target));
47+
var hasMembers = _state.AllUserDeclarations.Any(item => item.DeclarationType.HasFlag(DeclarationType.Member) && item.ParentDeclaration != null && item.ParentDeclaration.Equals(target));
4848

4949
// true if active code pane is for a class/document/form module
5050
var canExecute = ModuleTypes.Contains(Vbe.ActiveCodePane.CodeModule.Parent.Type) && target != null && hasMembers;

Rubberduck.Parsing/Rubberduck.Parsing.csproj

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -183,6 +183,8 @@
183183
<Compile Include="Symbols\IdentifierReferenceResolver.cs" />
184184
<Compile Include="Symbols\MemberProcessedEventArgs.cs" />
185185
<Compile Include="Symbols\ParameterDeclaration.cs" />
186+
<Compile Include="Symbols\ProjectDeclaration.cs" />
187+
<Compile Include="Symbols\ProjectReference.cs" />
186188
<Compile Include="Symbols\ReferencedDeclarationsCollector.cs" />
187189
<Compile Include="Symbols\SyntaxErrorException.cs" />
188190
<Compile Include="Nodes\CommentNode.cs" />

Rubberduck.Parsing/Symbols/DeclarationSymbolsListener.cs

Lines changed: 30 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -1,15 +1,13 @@
1-
using System;
2-
using System.Collections.Generic;
3-
using System.Linq;
4-
using System.Threading;
5-
using Antlr4.Runtime;
1+
using Antlr4.Runtime;
62
using Microsoft.Vbe.Interop;
3+
using Rubberduck.Parsing.Annotations;
74
using Rubberduck.Parsing.Grammar;
85
using Rubberduck.Parsing.Nodes;
96
using Rubberduck.Parsing.VBA;
107
using Rubberduck.VBEditor;
11-
using Rubberduck.VBEditor.Extensions;
12-
using Rubberduck.Parsing.Annotations;
8+
using System;
9+
using System.Collections.Generic;
10+
using System.Linq;
1311

1412
namespace Rubberduck.Parsing.Symbols
1513
{
@@ -26,14 +24,16 @@ public class DeclarationSymbolsListener : VBAParserBaseListener
2624
private readonly IEnumerable<CommentNode> _comments;
2725
private readonly IEnumerable<IAnnotation> _annotations;
2826
private readonly IDictionary<Tuple<string, DeclarationType>, Attributes> _attributes;
27+
private readonly HashSet<ReferencePriorityMap> _projectReferences;
2928

3029
public DeclarationSymbolsListener(
31-
QualifiedModuleName qualifiedName,
32-
Accessibility componentAccessibility,
33-
vbext_ComponentType type,
30+
QualifiedModuleName qualifiedName,
31+
Accessibility componentAccessibility,
32+
vbext_ComponentType type,
3433
IEnumerable<CommentNode> comments,
3534
IEnumerable<IAnnotation> annotations,
36-
IDictionary<Tuple<string, DeclarationType>, Attributes> attributes)
35+
IDictionary<Tuple<string, DeclarationType>, Attributes> attributes,
36+
HashSet<ReferencePriorityMap> projectReferences)
3737
{
3838
_qualifiedName = qualifiedName;
3939
_comments = comments;
@@ -46,6 +46,7 @@ public DeclarationSymbolsListener(
4646

4747
var project = _qualifiedName.Component.Collection.Parent;
4848
var projectQualifiedName = new QualifiedModuleName(project);
49+
_projectReferences = projectReferences;
4950

5051
_projectDeclaration = CreateProjectDeclaration(projectQualifiedName, project);
5152

@@ -59,7 +60,7 @@ public DeclarationSymbolsListener(
5960
_projectDeclaration,
6061
_projectDeclaration,
6162
_qualifiedName.Component.Name,
62-
false,
63+
false,
6364
false,
6465
componentAccessibility,
6566
declarationType,
@@ -69,13 +70,18 @@ public DeclarationSymbolsListener(
6970
SetCurrentScope();
7071
}
7172

72-
private static Declaration CreateProjectDeclaration(QualifiedModuleName projectQualifiedName, VBProject project)
73+
private Declaration CreateProjectDeclaration(QualifiedModuleName projectQualifiedName, VBProject project)
7374
{
74-
var declaration = new Declaration(
75-
projectQualifiedName.QualifyMemberName(project.Name),
76-
null, (Declaration) null, project.Name, false, false, Accessibility.Implicit, DeclarationType.Project, null,
77-
Selection.Home, false);
78-
return declaration;
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;
7985
}
8086

8187
private IEnumerable<IAnnotation> FindAnnotations()
@@ -156,7 +162,7 @@ private Declaration CreateDeclaration(string identifierName, string asTypeName,
156162
Declaration result;
157163
if (declarationType == DeclarationType.Parameter)
158164
{
159-
var argContext = (VBAParser.ArgContext) context;
165+
var argContext = (VBAParser.ArgContext)context;
160166
var isOptional = argContext.OPTIONAL() != null;
161167
var isByRef = argContext.BYREF() != null;
162168
var isParamArray = argContext.PARAMARRAY() != null;
@@ -277,8 +283,8 @@ public override void EnterFunctionStmt(VBAParser.FunctionStmtContext context)
277283
var name = identifier.GetText();
278284

279285
var asTypeClause = context.asTypeClause();
280-
var asTypeName = asTypeClause == null
281-
? Tokens.Variant
286+
var asTypeName = asTypeClause == null
287+
? Tokens.Variant
282288
: asTypeClause.type().GetText();
283289

284290
var declaration = CreateDeclaration(name, asTypeName, accessibility, DeclarationType.Function, context, context.ambiguousIdentifier().GetSelection());
@@ -392,10 +398,10 @@ public override void EnterDeclareStmt(VBAParser.DeclareStmtContext context)
392398
var hasReturnType = context.FUNCTION() != null;
393399

394400
var asTypeClause = context.asTypeClause();
395-
var asTypeName = hasReturnType
401+
var asTypeName = hasReturnType
396402
? asTypeClause == null
397403
? Tokens.Variant
398-
: asTypeClause.type().GetText()
404+
: asTypeClause.type().GetText()
399405
: null;
400406

401407
var selection = nameContext.GetSelection();
@@ -457,7 +463,7 @@ public override void EnterVariableSubStmt(VBAParser.VariableSubStmtContext conte
457463

458464
var withEvents = parent.WITHEVENTS() != null;
459465
var selfAssigned = asTypeClause != null && asTypeClause.NEW() != null;
460-
466+
461467
OnNewDeclaration(CreateDeclaration(name, asTypeName, accessibility, DeclarationType.Variable, context, context.ambiguousIdentifier().GetSelection(), selfAssigned, withEvents));
462468
}
463469

Lines changed: 43 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,43 @@
1+
using Rubberduck.VBEditor;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
5+
namespace Rubberduck.Parsing.Symbols
6+
{
7+
public sealed class ProjectDeclaration : Declaration
8+
{
9+
private readonly List<ProjectReference> _projectReferences;
10+
11+
public ProjectDeclaration(
12+
QualifiedMemberName qualifiedName,
13+
string name)
14+
: base(
15+
qualifiedName,
16+
null,
17+
(Declaration)null,
18+
name,
19+
false,
20+
false,
21+
Accessibility.Implicit,
22+
DeclarationType.Project,
23+
null,
24+
Selection.Home,
25+
false)
26+
{
27+
_projectReferences = new List<ProjectReference>();
28+
}
29+
30+
public IEnumerable<ProjectReference> ProjectReferences
31+
{
32+
get
33+
{
34+
return _projectReferences.OrderBy(reference => reference.Priority);
35+
}
36+
}
37+
38+
public void AddProjectReference(string referencedProjectId, int priority)
39+
{
40+
_projectReferences.Add(new ProjectReference(referencedProjectId, priority));
41+
}
42+
}
43+
}
Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,30 @@
1+
namespace Rubberduck.Parsing.Symbols
2+
{
3+
public sealed class ProjectReference
4+
{
5+
private readonly string _referencedProjectId;
6+
private readonly int _priority;
7+
8+
public ProjectReference(string referencedProjectId, int priority)
9+
{
10+
_priority = priority;
11+
_referencedProjectId = referencedProjectId;
12+
}
13+
14+
public string ReferencedProjectId
15+
{
16+
get
17+
{
18+
return _referencedProjectId;
19+
}
20+
}
21+
22+
public int Priority
23+
{
24+
get
25+
{
26+
return _priority;
27+
}
28+
}
29+
}
30+
}

Rubberduck.Parsing/Symbols/ReferencedDeclarationsCollector.cs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -90,11 +90,10 @@ public IEnumerable<Declaration> GetDeclarationsForReference(Reference reference)
9090
{
9191
var projectName = reference.Name;
9292
var path = reference.FullPath;
93-
94-
var projectQualifiedModuleName = new QualifiedModuleName(projectName, projectName);
93+
var projectQualifiedModuleName = new QualifiedModuleName(projectName, path, projectName);
9594
var projectQualifiedMemberName = new QualifiedMemberName(projectQualifiedModuleName, projectName);
9695

97-
var projectDeclaration = new Declaration(projectQualifiedMemberName, null, null, projectName, false, false, Accessibility.Global, DeclarationType.Project);
96+
var projectDeclaration = new ProjectDeclaration(projectQualifiedMemberName, projectName);
9897
yield return projectDeclaration;
9998

10099
ITypeLib typeLibrary;
@@ -134,7 +133,7 @@ public IEnumerable<Declaration> GetDeclarationsForReference(Reference reference)
134133
}
135134
else
136135
{
137-
typeQualifiedModuleName = new QualifiedModuleName(projectName, typeName);
136+
typeQualifiedModuleName = new QualifiedModuleName(projectName, path, typeName);
138137
typeQualifiedMemberName = new QualifiedMemberName(typeQualifiedModuleName, typeName);
139138
}
140139

Rubberduck.Parsing/VBA/ReferencePriorityMap.cs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -8,16 +8,16 @@ namespace Rubberduck.Parsing.VBA
88
/// </summary>
99
public class ReferencePriorityMap : Dictionary<string, int>
1010
{
11-
private readonly string _referenceId;
11+
private readonly string _referencedProjectId;
1212

13-
public ReferencePriorityMap(string referenceId)
13+
public ReferencePriorityMap(string referencedProjectId)
1414
{
15-
_referenceId = referenceId;
15+
_referencedProjectId = referencedProjectId;
1616
}
1717

18-
public string ReferenceId
18+
public string ReferencedProjectId
1919
{
20-
get { return _referenceId; }
20+
get { return _referencedProjectId; }
2121
}
2222

2323
public bool IsLoaded { get; set; }
@@ -27,12 +27,12 @@ public override bool Equals(object obj)
2727
var other = obj as ReferencePriorityMap;
2828
if (other == null) return false;
2929

30-
return other.ReferenceId == ReferenceId;
30+
return other.ReferencedProjectId == ReferencedProjectId;
3131
}
3232

3333
public override int GetHashCode()
3434
{
35-
return _referenceId.GetHashCode();
35+
return _referencedProjectId.GetHashCode();
3636
}
3737
}
3838
}

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 11 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -172,16 +172,15 @@ private void SyncComReferences(IReadOnlyList<VBProject> projects)
172172
{
173173
foreach (var vbProject in projects)
174174
{
175-
var projectId = vbProject.ProjectId();
175+
var projectId = QualifiedModuleName.GetProjectId(vbProject);
176176
for (var priority = 1; priority <= vbProject.References.Count; priority++)
177177
{
178178
var reference = vbProject.References.Item(priority);
179-
var referenceId = reference.ReferenceId();
180-
181-
var map = _references.SingleOrDefault(r => r.ReferenceId == referenceId);
179+
var referencedProjectId = QualifiedModuleName.GetProjectId(reference);
180+
var map = _references.SingleOrDefault(r => r.ReferencedProjectId == referencedProjectId);
182181
if (map == null)
183182
{
184-
map = new ReferencePriorityMap(referenceId) {{projectId, priority}};
183+
map = new ReferencePriorityMap(referencedProjectId) {{projectId, priority}};
185184
_references.Add(map);
186185
}
187186
else
@@ -201,9 +200,9 @@ private void SyncComReferences(IReadOnlyList<VBProject> projects)
201200
}
202201
}
203202

204-
var mappedIds = _references.Select(map => map.ReferenceId);
203+
var mappedIds = _references.Select(map => map.ReferencedProjectId);
205204
var unmapped = projects.SelectMany(project => project.References.Cast<Reference>())
206-
.Where(reference => !mappedIds.Contains(reference.ReferenceId()));
205+
.Where(reference => !mappedIds.Contains(QualifiedModuleName.GetProjectId(reference)));
207206
foreach (var reference in unmapped)
208207
{
209208
UnloadComReference(reference);
@@ -212,18 +211,15 @@ private void SyncComReferences(IReadOnlyList<VBProject> projects)
212211

213212
private void UnloadComReference(Reference reference)
214213
{
215-
var referenceId = reference.ReferenceId();
216-
var map = _references.SingleOrDefault(r => r.ReferenceId == referenceId);
214+
var referencedProjectId = QualifiedModuleName.GetProjectId(reference);
215+
var map = _references.SingleOrDefault(r => r.ReferencedProjectId == referencedProjectId);
217216
if (map == null || !map.IsLoaded)
218217
{
219218
// we're removing a reference we weren't tracking? ...this shouldn't happen.
220219
Debug.Assert(false);
221220
return;
222221
}
223-
224-
var projectId = reference.Collection.Parent.ProjectId();
225-
map.Remove(projectId);
226-
222+
map.Remove(referencedProjectId);
227223
if (!map.Any())
228224
{
229225
_references.Remove(map);
@@ -379,7 +375,7 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
379375
// cannot locate declarations in one pass *the way it's currently implemented*,
380376
// because the context in EnterSubStmt() doesn't *yet* have child nodes when the context enters.
381377
// so we need to EnterAmbiguousIdentifier() and evaluate the parent instead - this *might* work.
382-
var declarationsListener = new DeclarationSymbolsListener(qualifiedModuleName, Accessibility.Implicit, component.Type, _state.GetModuleComments(component), _state.GetModuleAnnotations(component),_state.GetModuleAttributes(component));
378+
var declarationsListener = new DeclarationSymbolsListener(qualifiedModuleName, Accessibility.Implicit, component.Type, _state.GetModuleComments(component), _state.GetModuleAnnotations(component),_state.GetModuleAttributes(component), _references);
383379
// TODO: should we unify the API? consider working like the other listeners instead of event-based
384380
declarationsListener.NewDeclaration += (sender, e) => _state.AddDeclaration(e.Declaration);
385381
declarationsListener.CreateModuleDeclarations();
@@ -401,8 +397,7 @@ private void ResolveReferences(DeclarationFinder finder, VBComponent component,
401397
return;
402398
}
403399
_state.SetModuleState(component, ParserState.Resolving);
404-
Debug.WriteLine("Resolving '{0}'... (thread {1})", component.Name, Thread.CurrentThread.ManagedThreadId);
405-
400+
Debug.WriteLine("Resolving '{0}'... (thread {1})", component.Name, Thread.CurrentThread.ManagedThreadId);
406401
var qualifiedName = new QualifiedModuleName(component);
407402
var resolver = new IdentifierReferenceResolver(qualifiedName, finder);
408403
var listener = new IdentifierReferenceListener(resolver);

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -99,7 +99,7 @@ public void RemoveProject(string projectId)
9999

100100
public void RemoveProject(VBProject project)
101101
{
102-
RemoveProject(project.ProjectId());
102+
RemoveProject(QualifiedModuleName.GetProjectId(project));
103103
}
104104

105105
public IEnumerable<VBProject> Projects
@@ -567,12 +567,12 @@ private static bool IsSelectedReference(QualifiedSelection selection, Identifier
567567
public void RemoveBuiltInDeclarations(Reference reference)
568568
{
569569
var projectName = reference.Name;
570-
var key = new QualifiedModuleName(projectName, projectName);
571-
570+
var path = reference.FullPath;
571+
var key = new QualifiedModuleName(projectName, path, projectName);
572572
ConcurrentDictionary<Declaration, byte> items;
573573
if (!_declarations.TryRemove(key, out items))
574574
{
575-
Debug.WriteLine("Could not remove declarations for removed reference '{0}' ({1}).", reference.Name, reference.ReferenceId());
575+
Debug.WriteLine("Could not remove declarations for removed reference '{0}' ({1}).", reference.Name, QualifiedModuleName.GetProjectId(reference));
576576
}
577577
}
578578
}

0 commit comments

Comments
 (0)