Skip to content

Commit 9508e47

Browse files
committed
added support for prioritized project references (ref. #1340)
1 parent ad79a9d commit 9508e47

File tree

7 files changed

+101
-51
lines changed

7 files changed

+101
-51
lines changed

RetailCoder.VBE/App.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -257,7 +257,7 @@ private void referencesSink_ReferenceAdded(object sender, DispatcherEventArgs<Re
257257
{
258258
Debug.WriteLine(string.Format("Reference '{0}' was added.", e.Item.Name));
259259
var state = _parser.State.Status;
260-
_parser.LoadComReference(e.Item);
260+
_parser.LoadNewComReferences();
261261
_parser.State.SetModuleState(state);
262262
}
263263

Rubberduck.Parsing/IRubberduckParser.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ namespace Rubberduck.Parsing
1010
public interface IRubberduckParser
1111
{
1212
RubberduckParserState State { get; }
13-
void LoadComReference(Reference item);
13+
void LoadNewComReferences();
1414
void UnloadComReference(Reference reference);
1515
void ParseComponent(VBComponent component, TokenStreamRewriter rewriter = null);
1616
Task ParseAsync(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null);

Rubberduck.Parsing/Rubberduck.Parsing.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -210,6 +210,7 @@
210210
<Compile Include="VBA\Nodes\ProcedureNode.cs" />
211211
<Compile Include="VBA\ParseErrorEventArgs.cs" />
212212
<Compile Include="VBA\ParserState.cs" />
213+
<Compile Include="VBA\ReferencePriorityMap.cs" />
213214
<Compile Include="VBA\RubberduckParser.cs" />
214215
<Compile Include="VBA\RubberduckParserState.cs" />
215216
<Compile Include="VBA\StringExtensions.cs" />
Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,38 @@
1+
using System.Collections.Generic;
2+
using Microsoft.Vbe.Interop;
3+
4+
namespace Rubberduck.Parsing.VBA
5+
{
6+
/// <summary>
7+
/// A <c>Dictionary</c> keyed with a <see cref="VBProject"/>'s ID and valued with an <see cref="int"/> representing a <see cref="Reference"/>'s priority for that project.
8+
/// </summary>
9+
public class ReferencePriorityMap : Dictionary<string, int>
10+
{
11+
private readonly string _referenceId;
12+
13+
public ReferencePriorityMap(string referenceId)
14+
{
15+
_referenceId = referenceId;
16+
}
17+
18+
public string ReferenceId
19+
{
20+
get { return _referenceId; }
21+
}
22+
23+
public bool IsLoaded { get; set; }
24+
25+
public override bool Equals(object obj)
26+
{
27+
var other = obj as ReferencePriorityMap;
28+
if (other == null) return false;
29+
30+
return other.ReferenceId == ReferenceId;
31+
}
32+
33+
public override int GetHashCode()
34+
{
35+
return _referenceId.GetHashCode();
36+
}
37+
}
38+
}

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 46 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -12,9 +12,9 @@
1212
using System.Globalization;
1313
using Rubberduck.Parsing.Preprocessing;
1414
using System.Diagnostics;
15-
using Rubberduck.Common;
1615
using Rubberduck.Parsing.Grammar;
1716
using Rubberduck.Parsing.Nodes;
17+
using Rubberduck.VBEditor.Extensions;
1818

1919
namespace Rubberduck.Parsing.VBA
2020
{
@@ -27,6 +27,7 @@ public RubberduckParserState State
2727
return _state;
2828
}
2929
}
30+
3031
private CancellationTokenSource _central = new CancellationTokenSource();
3132
private CancellationTokenSource _resolverTokenSource; // linked to _central later
3233
private readonly ConcurrentDictionary<VBComponent, Tuple<Task, CancellationTokenSource>> _currentTasks =
@@ -72,7 +73,6 @@ private void StateOnStateChanged(object sender, EventArgs e)
7273

7374
private void ReparseRequested(object sender, ParseRequestEventArgs e)
7475
{
75-
_force = false;
7676
if (e.IsFullReparseRequest)
7777
{
7878
Cancel();
@@ -85,10 +85,8 @@ private void ReparseRequested(object sender, ParseRequestEventArgs e)
8585
}
8686
}
8787

88-
private bool _force;
8988
public void Parse()
9089
{
91-
_force = true;
9290
if (!_state.Projects.Any())
9391
{
9492
foreach (var project in _vbe.VBProjects.Cast<VBProject>())
@@ -131,7 +129,6 @@ public void Parse()
131129
/// </summary>
132130
private void ParseAll()
133131
{
134-
_force = false;
135132
var projects = _state.Projects
136133
.Where(project => project.Protection == vbext_ProjectProtection.vbext_pp_none)
137134
.ToList();
@@ -161,58 +158,65 @@ private void ParseAll()
161158
}
162159
}
163160

164-
private readonly HashSet<Guid> _loadedReferences = new HashSet<Guid>();
161+
private readonly HashSet<ReferencePriorityMap> _references = new HashSet<ReferencePriorityMap>();
162+
165163
private void LoadComReferences(IEnumerable<VBProject> projects)
166164
{
167-
var references = projects.SelectMany(p => p.References.Cast<Reference>()).ToList();
168-
var newReferences = references
169-
.Select(reference => new {Guid = new Guid(reference.Guid), Reference = reference})
170-
.Where(item => !_loadedReferences.Contains(item.Guid));
171-
172-
for (var i = 0; i < references.Count; i++)
165+
foreach (var vbProject in projects)
173166
{
174-
175-
}
167+
var projectId = vbProject.ProjectId();
168+
for (var priority = 0; priority < vbProject.References.Count; priority++)
169+
{
170+
var reference = vbProject.References.Item(priority);
171+
var referenceId = reference.ReferenceId();
176172

177-
foreach (var item in newReferences)
178-
{
179-
LoadComReference(item.Reference);
173+
var map = _references.SingleOrDefault(r => r.ReferenceId == referenceId);
174+
if (map == null)
175+
{
176+
map = new ReferencePriorityMap(referenceId) {{projectId, priority}};
177+
_references.Add(map);
178+
}
179+
else
180+
{
181+
map[projectId] = priority;
182+
}
183+
184+
if (!map.IsLoaded)
185+
{
186+
var items = _comReflector.GetDeclarationsForReference(reference).ToList();
187+
foreach (var declaration in items)
188+
{
189+
_state.AddDeclaration(declaration);
190+
}
191+
map.IsLoaded = true;
192+
}
193+
}
180194
}
181195
}
182196

183-
public void LoadComReference(Reference item)
197+
public void LoadNewComReferences()
184198
{
185-
var guid = new Guid(item.Guid);
186-
if (_loadedReferences.Contains(guid))
187-
{
188-
return;
189-
}
190-
191-
var items = _comReflector.GetDeclarationsForReference(item).ToList();
192-
foreach (var declaration in items)
193-
{
194-
_state.AddDeclaration(declaration);
195-
}
196-
197-
_loadedReferences.Add(new Guid(item.Guid));
199+
LoadComReferences(_state.Projects);
198200
}
199201

200202
public void UnloadComReference(Reference reference)
201203
{
202-
var projects = _state.Projects
203-
.Where(project => project.Protection == vbext_ProjectProtection.vbext_pp_none)
204-
.ToList();
204+
var referenceId = reference.ReferenceId();
205+
var map = _references.SingleOrDefault(r => r.ReferenceId == referenceId);
206+
if (map == null || !map.IsLoaded)
207+
{
208+
// we're removing a reference we weren't tracking? ...this shouldn't happen.
209+
Debug.Assert(false);
210+
return;
211+
}
205212

206-
var references = projects.SelectMany(p => p.References.Cast<Reference>()).ToList();
207-
var target = references
208-
.Select(item => new { Guid = new Guid(item.Guid), Reference = item })
209-
.SingleOrDefault(item => _loadedReferences.Contains(item.Guid) && reference.Guid == item.Guid.ToString());
213+
var projectId = reference.Collection.Parent.ProjectId();
214+
map.Remove(projectId);
210215

211-
if (target != null)
216+
if (!map.Any())
212217
{
213-
_state.RemoveBuiltInDeclarations(target.Reference);
214-
var guid = new Guid(reference.Guid);
215-
_loadedReferences.Remove(guid);
218+
_references.Remove(map);
219+
_state.RemoveBuiltInDeclarations(reference);
216220
}
217221
}
218222

Rubberduck.Parsing/VBA/RubberduckParserState.cs

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

100100
public void RemoveProject(VBProject project)
101101
{
102-
var projectId = project.HelpFile;
103-
RemoveProject(projectId);
104-
105-
// note: attempt to fix ghost projects
106-
projectId = project.Name;
107-
RemoveProject(projectId);
102+
RemoveProject(project.ProjectId());
108103
}
109104

110105
public IEnumerable<VBProject> Projects
@@ -577,7 +572,7 @@ public void RemoveBuiltInDeclarations(Reference reference)
577572
ConcurrentDictionary<Declaration, byte> items;
578573
if (!_declarations.TryRemove(key, out items))
579574
{
580-
Debug.WriteLine("Could not remove declarations for removed reference '{0}' ({1}).", reference.Name, reference.Guid);
575+
Debug.WriteLine("Could not remove declarations for removed reference '{0}' ({1}).", reference.Name, reference.ReferenceId());
581576
}
582577
}
583578
}

Rubberduck.VBEEditor/Extensions/VbProjectExtensions.cs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,18 @@ namespace Rubberduck.VBEditor.Extensions
1010
{
1111
public static class ProjectExtensions
1212
{
13+
public static string ProjectId(this VBProject project)
14+
{
15+
return project.HelpFile;
16+
}
17+
18+
public static string ReferenceId(this Reference reference)
19+
{
20+
return string.IsNullOrEmpty(reference.Guid)
21+
? reference.FullPath
22+
: reference.Guid;
23+
}
24+
1325
public static IEnumerable<string> ComponentNames(this VBProject project)
1426
{
1527
return project.VBComponents.Cast<VBComponent>().Select(component => component.Name);

0 commit comments

Comments
 (0)