Skip to content

Commit

Permalink
Merge pull request #1341 from retailcoder/next
Browse files Browse the repository at this point in the history
Stabilized parser
  • Loading branch information
retailcoder committed Apr 21, 2016
2 parents 68434fa + 28baafc commit 6969fde
Show file tree
Hide file tree
Showing 7 changed files with 108 additions and 95 deletions.
38 changes: 1 addition & 37 deletions RetailCoder.VBE/App.cs
Original file line number Diff line number Diff line change
Expand Up @@ -187,6 +187,7 @@ async void sink_ProjectRemoved(object sender, DispatcherEventArgs<VBProject> e)
async void sink_ProjectAdded(object sender, DispatcherEventArgs<VBProject> e)
{
var sink = (VBProjectsEventsSink)sender;
RegisterComponentsEventSink(e, sink);
_parser.State.AddProject(e.Item);

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

Debug.WriteLine(string.Format("Project '{0}' was added.", e.Item.Name));
RegisterComponentsEventSink(e, sink);
RegisterReferencesEventsSink(e, sink);

_parser.State.OnParseRequested(sender);
}

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

private void RegisterReferencesEventsSink(DispatcherEventArgs<VBProject> e, VBProjectsEventsSink sink)
{
var connectionPointContainer = (IConnectionPointContainer)e.Item.References;
var interfaceId = typeof(_dispReferencesEvents).GUID;

IConnectionPoint connectionPoint;
connectionPointContainer.FindConnectionPoint(ref interfaceId, out connectionPoint);

var referencesSink = new ReferencesEventsSink();
referencesSink.ReferenceAdded += referencesSink_ReferenceAdded;
referencesSink.ReferenceRemoved += referencesSink_ReferenceRemoved;
_referencesEventsSinks.Add(sink, referencesSink);

int cookie;
connectionPoint.Advise(referencesSink, out cookie);
_referencesEventsConnectionPoints.Add(sink, Tuple.Create(connectionPoint, cookie));
}

private void referencesSink_ReferenceRemoved(object sender, DispatcherEventArgs<Reference> e)
{
Debug.WriteLine(string.Format("Reference '{0}' was removed.", e.Item.Name));
var state = _parser.State.Status;
_parser.UnloadComReference(e.Item);
_parser.State.SetModuleState(state);
}

private void referencesSink_ReferenceAdded(object sender, DispatcherEventArgs<Reference> e)
{
Debug.WriteLine(string.Format("Reference '{0}' was added.", e.Item.Name));
var state = _parser.State.Status;
_parser.LoadComReference(e.Item);
_parser.State.SetModuleState(state);
}

async void sink_ComponentSelected(object sender, DispatcherEventArgs<VBComponent> e)
{
if (!_parser.State.AllDeclarations.Any())
Expand Down
11 changes: 0 additions & 11 deletions Rubberduck.Parsing/IRubberduckParser.cs
Original file line number Diff line number Diff line change
@@ -1,20 +1,9 @@
using System;
using System.Threading;
using System.Threading.Tasks;
using Antlr4.Runtime;
using Microsoft.Vbe.Interop;
using Rubberduck.Parsing.VBA;

namespace Rubberduck.Parsing
{
public interface IRubberduckParser
{
RubberduckParserState State { get; }
void LoadComReference(Reference item);
void UnloadComReference(Reference reference);
void ParseComponent(VBComponent component, TokenStreamRewriter rewriter = null);
Task ParseAsync(VBComponent component, CancellationToken token, TokenStreamRewriter rewriter = null);
void Cancel(VBComponent component = null);
void Resolve(CancellationToken token);
}
}
1 change: 1 addition & 0 deletions Rubberduck.Parsing/Rubberduck.Parsing.csproj
Original file line number Diff line number Diff line change
Expand Up @@ -210,6 +210,7 @@
<Compile Include="VBA\Nodes\ProcedureNode.cs" />
<Compile Include="VBA\ParseErrorEventArgs.cs" />
<Compile Include="VBA\ParserState.cs" />
<Compile Include="VBA\ReferencePriorityMap.cs" />
<Compile Include="VBA\RubberduckParser.cs" />
<Compile Include="VBA\RubberduckParserState.cs" />
<Compile Include="VBA\StringExtensions.cs" />
Expand Down
38 changes: 38 additions & 0 deletions Rubberduck.Parsing/VBA/ReferencePriorityMap.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,38 @@
using System.Collections.Generic;
using Microsoft.Vbe.Interop;

namespace Rubberduck.Parsing.VBA
{
/// <summary>
/// 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.
/// </summary>
public class ReferencePriorityMap : Dictionary<string, int>
{
private readonly string _referenceId;

public ReferencePriorityMap(string referenceId)
{
_referenceId = referenceId;
}

public string ReferenceId
{
get { return _referenceId; }
}

public bool IsLoaded { get; set; }

public override bool Equals(object obj)
{
var other = obj as ReferencePriorityMap;
if (other == null) return false;

return other.ReferenceId == ReferenceId;
}

public override int GetHashCode()
{
return _referenceId.GetHashCode();
}
}
}
94 changes: 54 additions & 40 deletions Rubberduck.Parsing/VBA/RubberduckParser.cs
Original file line number Diff line number Diff line change
Expand Up @@ -12,9 +12,9 @@
using System.Globalization;
using Rubberduck.Parsing.Preprocessing;
using System.Diagnostics;
using Rubberduck.Common;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Nodes;
using Rubberduck.VBEditor.Extensions;

namespace Rubberduck.Parsing.VBA
{
Expand All @@ -27,6 +27,7 @@ public RubberduckParserState State
return _state;
}
}

private CancellationTokenSource _central = new CancellationTokenSource();
private CancellationTokenSource _resolverTokenSource; // linked to _central later
private readonly ConcurrentDictionary<VBComponent, Tuple<Task, CancellationTokenSource>> _currentTasks =
Expand Down Expand Up @@ -72,7 +73,6 @@ private void StateOnStateChanged(object sender, EventArgs e)

private void ReparseRequested(object sender, ParseRequestEventArgs e)
{
_force = false;
if (e.IsFullReparseRequest)
{
Cancel();
Expand All @@ -85,10 +85,8 @@ private void ReparseRequested(object sender, ParseRequestEventArgs e)
}
}

private bool _force;
public void Parse()
{
_force = true;
if (!_state.Projects.Any())
{
foreach (var project in _vbe.VBProjects.Cast<VBProject>())
Expand Down Expand Up @@ -131,21 +129,30 @@ public void Parse()
/// </summary>
private void ParseAll()
{
_force = false;
var projects = _state.Projects
.Where(project => project.Protection == vbext_ProjectProtection.vbext_pp_none)
.ToList();

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

_state.SetModuleState(ParserState.LoadingReference);
_state.SetModuleState(ParserState.LoadingReference); // todo: change that to a simple statusbar text update
LoadComReferences(projects);

if (!modified.Any())
{
return;
}

foreach (var component in modified)
{
_state.SetModuleState(component, ParserState.Pending);
}
foreach (var component in unchanged)
{
_state.SetModuleState(component, ParserState.Parsed);
}

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

foreach (var vbComponent in modified)
{
while (!_state.ClearDeclarations(vbComponent)) { }

ParseAsync(vbComponent, CancellationToken.None);
}
}

private readonly HashSet<Guid> _loadedReferences = new HashSet<Guid>();
private readonly HashSet<ReferencePriorityMap> _references = new HashSet<ReferencePriorityMap>();

private void LoadComReferences(IEnumerable<VBProject> projects)
{
var references = projects.SelectMany(p => p.References.Cast<Reference>()).ToList();
var newReferences = references
.Select(reference => new {Guid = new Guid(reference.Guid), Reference = reference})
.Where(item => !_loadedReferences.Contains(item.Guid));

foreach (var item in newReferences)
foreach (var vbProject in projects)
{
LoadComReference(item.Reference);
}
}
var projectId = vbProject.ProjectId();
for (var priority = 1; priority <= vbProject.References.Count; priority++)
{
var reference = vbProject.References.Item(priority);
var referenceId = reference.ReferenceId();

public void LoadComReference(Reference item)
{
var guid = new Guid(item.Guid);
if (_loadedReferences.Contains(guid))
{
return;
}
var map = _references.SingleOrDefault(r => r.ReferenceId == referenceId);
if (map == null)
{
map = new ReferencePriorityMap(referenceId) {{projectId, priority}};
_references.Add(map);
}
else
{
map[projectId] = priority;
}

var items = _comReflector.GetDeclarationsForReference(item).ToList();
foreach (var declaration in items)
{
_state.AddDeclaration(declaration);
if (!map.IsLoaded)
{
var items = _comReflector.GetDeclarationsForReference(reference).ToList();
foreach (var declaration in items)
{
_state.AddDeclaration(declaration);
}
map.IsLoaded = true;
}
}
}

_loadedReferences.Add(new Guid(item.Guid));
}

public void UnloadComReference(Reference reference)
{
var projects = _state.Projects
.Where(project => project.Protection == vbext_ProjectProtection.vbext_pp_none)
.ToList();
var referenceId = reference.ReferenceId();
var map = _references.SingleOrDefault(r => r.ReferenceId == referenceId);
if (map == null || !map.IsLoaded)
{
// we're removing a reference we weren't tracking? ...this shouldn't happen.
Debug.Assert(false);
return;
}

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

if (target != null)
if (!map.Any())
{
_state.RemoveBuiltInDeclarations(target.Reference);
_references.Remove(map);
_state.RemoveBuiltInDeclarations(reference);
}
}

Expand Down
9 changes: 2 additions & 7 deletions Rubberduck.Parsing/VBA/RubberduckParserState.cs
Original file line number Diff line number Diff line change
Expand Up @@ -99,12 +99,7 @@ public void RemoveProject(string projectId)

public void RemoveProject(VBProject project)
{
var projectId = project.HelpFile;
RemoveProject(projectId);

// note: attempt to fix ghost projects
projectId = project.Name;
RemoveProject(projectId);
RemoveProject(project.ProjectId());
}

public IEnumerable<VBProject> Projects
Expand Down Expand Up @@ -577,7 +572,7 @@ public void RemoveBuiltInDeclarations(Reference reference)
ConcurrentDictionary<Declaration, byte> items;
if (!_declarations.TryRemove(key, out items))
{
Debug.WriteLine("Could not remove declarations for removed reference '{0}' ({1}).", reference.Name, reference.Guid);
Debug.WriteLine("Could not remove declarations for removed reference '{0}' ({1}).", reference.Name, reference.ReferenceId());
}
}
}
Expand Down
12 changes: 12 additions & 0 deletions Rubberduck.VBEEditor/Extensions/VbProjectExtensions.cs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,18 @@ namespace Rubberduck.VBEditor.Extensions
{
public static class ProjectExtensions
{
public static string ProjectId(this VBProject project)
{
return project.HelpFile;
}

public static string ReferenceId(this Reference reference)
{
return string.IsNullOrEmpty(reference.Guid)
? reference.FullPath
: reference.Guid;
}

public static IEnumerable<string> ComponentNames(this VBProject project)
{
return project.VBComponents.Cast<VBComponent>().Select(component => component.Name);
Expand Down

0 comments on commit 6969fde

Please sign in to comment.