Skip to content

Commit 6969fde

Browse files
committed
Merge pull request #1341 from retailcoder/next
Stabilized parser
2 parents 68434fa + 28baafc commit 6969fde

File tree

7 files changed

+108
-95
lines changed

7 files changed

+108
-95
lines changed

RetailCoder.VBE/App.cs

Lines changed: 1 addition & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -187,6 +187,7 @@ async void sink_ProjectRemoved(object sender, DispatcherEventArgs<VBProject> e)
187187
async void sink_ProjectAdded(object sender, DispatcherEventArgs<VBProject> e)
188188
{
189189
var sink = (VBProjectsEventsSink)sender;
190+
RegisterComponentsEventSink(e, sink);
190191
_parser.State.AddProject(e.Item);
191192

192193
if (!_parser.State.AllDeclarations.Any())
@@ -198,9 +199,6 @@ async void sink_ProjectAdded(object sender, DispatcherEventArgs<VBProject> e)
198199
}
199200

200201
Debug.WriteLine(string.Format("Project '{0}' was added.", e.Item.Name));
201-
RegisterComponentsEventSink(e, sink);
202-
RegisterReferencesEventsSink(e, sink);
203-
204202
_parser.State.OnParseRequested(sender);
205203
}
206204

@@ -227,40 +225,6 @@ private void RegisterComponentsEventSink(DispatcherEventArgs<VBProject> e, VBPro
227225
_componentsEventsConnectionPoints.Add(sink, Tuple.Create(connectionPoint, cookie));
228226
}
229227

230-
private void RegisterReferencesEventsSink(DispatcherEventArgs<VBProject> e, VBProjectsEventsSink sink)
231-
{
232-
var connectionPointContainer = (IConnectionPointContainer)e.Item.References;
233-
var interfaceId = typeof(_dispReferencesEvents).GUID;
234-
235-
IConnectionPoint connectionPoint;
236-
connectionPointContainer.FindConnectionPoint(ref interfaceId, out connectionPoint);
237-
238-
var referencesSink = new ReferencesEventsSink();
239-
referencesSink.ReferenceAdded += referencesSink_ReferenceAdded;
240-
referencesSink.ReferenceRemoved += referencesSink_ReferenceRemoved;
241-
_referencesEventsSinks.Add(sink, referencesSink);
242-
243-
int cookie;
244-
connectionPoint.Advise(referencesSink, out cookie);
245-
_referencesEventsConnectionPoints.Add(sink, Tuple.Create(connectionPoint, cookie));
246-
}
247-
248-
private void referencesSink_ReferenceRemoved(object sender, DispatcherEventArgs<Reference> e)
249-
{
250-
Debug.WriteLine(string.Format("Reference '{0}' was removed.", e.Item.Name));
251-
var state = _parser.State.Status;
252-
_parser.UnloadComReference(e.Item);
253-
_parser.State.SetModuleState(state);
254-
}
255-
256-
private void referencesSink_ReferenceAdded(object sender, DispatcherEventArgs<Reference> e)
257-
{
258-
Debug.WriteLine(string.Format("Reference '{0}' was added.", e.Item.Name));
259-
var state = _parser.State.Status;
260-
_parser.LoadComReference(e.Item);
261-
_parser.State.SetModuleState(state);
262-
}
263-
264228
async void sink_ComponentSelected(object sender, DispatcherEventArgs<VBComponent> e)
265229
{
266230
if (!_parser.State.AllDeclarations.Any())
Lines changed: 0 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,20 +1,9 @@
1-
using System;
2-
using System.Threading;
3-
using System.Threading.Tasks;
4-
using Antlr4.Runtime;
5-
using Microsoft.Vbe.Interop;
61
using Rubberduck.Parsing.VBA;
72

83
namespace Rubberduck.Parsing
94
{
105
public interface IRubberduckParser
116
{
127
RubberduckParserState State { get; }
13-
void LoadComReference(Reference item);
14-
void UnloadComReference(Reference reference);
15-
void ParseComponent(VBComponent component, TokenStreamRewriter rewriter = null);
16-
Task ParseAsync(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null);
17-
void Cancel(VBComponent component = null);
18-
void Resolve(CancellationToken token);
198
}
209
}

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: 54 additions & 40 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,21 +129,30 @@ 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();
138135

139136
var components = projects.SelectMany(p => p.VBComponents.Cast<VBComponent>()).ToList();
140137
var modified = components.Where(_state.IsModified).ToList();
138+
var unchanged = components.Where(c => !_state.IsModified(c)).ToList();
141139

142-
_state.SetModuleState(ParserState.LoadingReference);
140+
_state.SetModuleState(ParserState.LoadingReference); // todo: change that to a simple statusbar text update
143141
LoadComReferences(projects);
144142

143+
if (!modified.Any())
144+
{
145+
return;
146+
}
147+
145148
foreach (var component in modified)
146149
{
147150
_state.SetModuleState(component, ParserState.Pending);
148151
}
152+
foreach (var component in unchanged)
153+
{
154+
_state.SetModuleState(component, ParserState.Parsed);
155+
}
149156

150157
// invalidation cleanup should go into ParseAsync?
151158
foreach (var invalidated in _componentAttributes.Keys.Except(components))
@@ -155,57 +162,64 @@ private void ParseAll()
155162

156163
foreach (var vbComponent in modified)
157164
{
158-
while (!_state.ClearDeclarations(vbComponent)) { }
159-
160165
ParseAsync(vbComponent, CancellationToken.None);
161166
}
162167
}
163168

164-
private readonly HashSet<Guid> _loadedReferences = new HashSet<Guid>();
169+
private readonly HashSet<ReferencePriorityMap> _references = new HashSet<ReferencePriorityMap>();
170+
165171
private void LoadComReferences(IEnumerable<VBProject> projects)
166172
{
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-
foreach (var item in newReferences)
173+
foreach (var vbProject in projects)
173174
{
174-
LoadComReference(item.Reference);
175-
}
176-
}
175+
var projectId = vbProject.ProjectId();
176+
for (var priority = 1; priority <= vbProject.References.Count; priority++)
177+
{
178+
var reference = vbProject.References.Item(priority);
179+
var referenceId = reference.ReferenceId();
177180

178-
public void LoadComReference(Reference item)
179-
{
180-
var guid = new Guid(item.Guid);
181-
if (_loadedReferences.Contains(guid))
182-
{
183-
return;
184-
}
181+
var map = _references.SingleOrDefault(r => r.ReferenceId == referenceId);
182+
if (map == null)
183+
{
184+
map = new ReferencePriorityMap(referenceId) {{projectId, priority}};
185+
_references.Add(map);
186+
}
187+
else
188+
{
189+
map[projectId] = priority;
190+
}
185191

186-
var items = _comReflector.GetDeclarationsForReference(item).ToList();
187-
foreach (var declaration in items)
188-
{
189-
_state.AddDeclaration(declaration);
192+
if (!map.IsLoaded)
193+
{
194+
var items = _comReflector.GetDeclarationsForReference(reference).ToList();
195+
foreach (var declaration in items)
196+
{
197+
_state.AddDeclaration(declaration);
198+
}
199+
map.IsLoaded = true;
200+
}
201+
}
190202
}
191-
192-
_loadedReferences.Add(new Guid(item.Guid));
193203
}
194204

195205
public void UnloadComReference(Reference reference)
196206
{
197-
var projects = _state.Projects
198-
.Where(project => project.Protection == vbext_ProjectProtection.vbext_pp_none)
199-
.ToList();
207+
var referenceId = reference.ReferenceId();
208+
var map = _references.SingleOrDefault(r => r.ReferenceId == referenceId);
209+
if (map == null || !map.IsLoaded)
210+
{
211+
// we're removing a reference we weren't tracking? ...this shouldn't happen.
212+
Debug.Assert(false);
213+
return;
214+
}
200215

201-
var references = projects.SelectMany(p => p.References.Cast<Reference>()).ToList();
202-
var target = references
203-
.Select(item => new { Guid = new Guid(item.Guid), Reference = item })
204-
.SingleOrDefault(item => _loadedReferences.Contains(item.Guid) && reference.Guid == item.Guid.ToString());
216+
var projectId = reference.Collection.Parent.ProjectId();
217+
map.Remove(projectId);
205218

206-
if (target != null)
219+
if (!map.Any())
207220
{
208-
_state.RemoveBuiltInDeclarations(target.Reference);
221+
_references.Remove(map);
222+
_state.RemoveBuiltInDeclarations(reference);
209223
}
210224
}
211225

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)