Skip to content

Commit 36bfaf2

Browse files
committed
fixed merge artifacts
1 parent 4f4cbd7 commit 36bfaf2

File tree

1 file changed

+16
-117
lines changed

1 file changed

+16
-117
lines changed

Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 16 additions & 117 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,6 @@
1818
using System.Runtime.InteropServices;
1919
using Rubberduck.VBEditor.Application;
2020
using Rubberduck.VBEditor.Extensions;
21-
using Rubberduck.VBEditor.SafeComWrappers;
2221

2322
// ReSharper disable LoopCanBeConvertedToQuery
2423

@@ -62,7 +61,7 @@ public ParseCoordinator(
6261
_preprocessorFactory = preprocessorFactory;
6362
_customDeclarationLoaders = customDeclarationLoaders;
6463
_isTestScope = isTestScope;
65-
_serializedDeclarationsPath = serializedDeclarationsPath
64+
_serializedDeclarationsPath = serializedDeclarationsPath
6665
?? Path.Combine(Environment.GetFolderPath(Environment.SpecialFolder.ApplicationData), "Rubberduck", "declarations");
6766
_hostApp = _vbe.HostApplication();
6867

@@ -72,7 +71,7 @@ public ParseCoordinator(
7271
// Do not access this from anywhere but ReparseRequested.
7372
// ReparseRequested needs to have a reference to all the cancellation tokens,
7473
// but the cancelees need to use their own token.
75-
private readonly List<CancellationTokenSource> _cancellationTokens = new List<CancellationTokenSource> {new CancellationTokenSource()};
74+
private readonly List<CancellationTokenSource> _cancellationTokens = new List<CancellationTokenSource> { new CancellationTokenSource() };
7675

7776
private void ReparseRequested(object sender, EventArgs e)
7877
{
@@ -183,7 +182,6 @@ private void ExecuteCommonParseActivities(List<IVBComponent> toParse, Cancellati
183182

184183
if (token.IsCancellationRequested || State.Status >= ParserState.Error)
185184
{
186-
_state.IsEnabled = true;
187185
return;
188186
}
189187

@@ -192,7 +190,6 @@ private void ExecuteCommonParseActivities(List<IVBComponent> toParse, Cancellati
192190

193191
if (token.IsCancellationRequested || State.Status >= ParserState.Error)
194192
{
195-
_state.IsEnabled = true;
196193
return;
197194
}
198195

@@ -224,7 +221,7 @@ private void SetModuleStates(List<IVBComponent> components, ParserState parserSt
224221
options.MaxDegreeOfParallelism = _maxDegreeOfModuleStateChangeParallelism;
225222

226223
Parallel.ForEach(components, options, component => State.SetModuleState(component, parserState, null, false));
227-
224+
228225
State.EvaluateParserState();
229226
}
230227

@@ -413,7 +410,7 @@ private void ResolveAllReferences(CancellationToken token)
413410
{
414411
var components = State.ParseTrees.Select(kvp => kvp.Key.Component).ToList();
415412
SetModuleStates(components, ParserState.ResolvingReferences);
416-
413+
417414
ExecuteCompilationPasses();
418415

419416
var options = new ParallelOptions();
@@ -474,7 +471,7 @@ private void ResolveReferences(DeclarationFinder finder, IVBComponent component,
474471
watch.ElapsedMilliseconds, Thread.CurrentThread.ManagedThreadId);
475472

476473
//Evaluation of the overall status has to be defered to allow processing of undeclared variables before setting the ready state.
477-
State.SetModuleState(component, ParserState.Ready,null,false);
474+
State.SetModuleState(component, ParserState.Ready, null, false);
478475
}
479476
catch (Exception exception)
480477
{
@@ -500,16 +497,16 @@ private void AddUndeclaredVariablesToDeclarations()
500497
private void ParseAll(object requestor, CancellationTokenSource token)
501498
{
502499
State.RefreshProjects(_vbe);
503-
500+
504501
var components = State.Projects.SelectMany(project => project.VBComponents).ToList();
505502

506-
var componentsRemoved = ClearStateCacheForRemovedComponents(components);
503+
var componentsRemoved = ClearStateCashForRemovedComponents(components);
507504

508505
// invalidation cleanup should go into ParseAsync?
509506
CleanUpComponentAttributes(components);
510507

511-
var toParse = components.Where(component => State.IsNewOrModified(component)).ToList();
512-
508+
var toParse = components.Where(component => State.IsNewOrModified(component)).ToList();
509+
513510
if (toParse.Count == 0)
514511
{
515512
if (componentsRemoved) // trigger UI updates
@@ -525,10 +522,10 @@ private void ParseAll(object requestor, CancellationTokenSource token)
525522
}
526523

527524
/// <summary>
528-
/// Clears state cache for removed components.
525+
/// Clears state cach for removed components.
529526
/// Returns whether components have been removed.
530527
/// </summary>
531-
private bool ClearStateCacheForRemovedComponents(List<IVBComponent> components)
528+
private bool ClearStateCashForRemovedComponents(List<IVBComponent> components)
532529
{
533530
var removedModuledecalrations = RemovedModuleDeclarations(components);
534531
var componentRemoved = removedModuledecalrations.Any();
@@ -591,7 +588,7 @@ private string GetReferenceProjectId(IReference reference, IReadOnlyList<IVBProj
591588
Logger.Warn(e);
592589
}
593590
}
594-
591+
595592
if (project != null)
596593
{
597594
if (string.IsNullOrEmpty(project.ProjectId))
@@ -620,7 +617,7 @@ private void SyncComReferences(IReadOnlyList<IVBProject> projects)
620617
var reference = references[priority];
621618
if (reference.IsBroken)
622619
{
623-
continue;
620+
continue;
624621
}
625622

626623
// skip loading Rubberduck.tlb (GUID is defined in AssemblyInfo.cs)
@@ -642,7 +639,7 @@ private void SyncComReferences(IReadOnlyList<IVBProject> projects)
642639

643640
if (map == null)
644641
{
645-
map = new ReferencePriorityMap(referencedProjectId) {{projectId, priority}};
642+
map = new ReferencePriorityMap(referencedProjectId) { { projectId, priority } };
646643
_projectReferences.Add(map);
647644
}
648645
else
@@ -734,7 +731,7 @@ private void UnloadComReference(IReference reference, IReadOnlyList<IVBProject>
734731
map = map != null ? null : item;
735732
}
736733
}
737-
734+
738735
if (map == null || !map.IsLoaded)
739736
{
740737
// we're removing a reference we weren't tracking? ...this shouldn't happen.
@@ -750,108 +747,10 @@ private void UnloadComReference(IReference reference, IReadOnlyList<IVBProject>
750747
}
751748

752749

753-
private readonly ConcurrentDictionary<string, Declaration> _projectDeclarations = new ConcurrentDictionary<string, Declaration>();
754-
private void ResolveDeclarations(IVBComponent component, IParseTree tree)
755-
{
756-
if (component == null) { return; }
757-
758-
var qualifiedModuleName = new QualifiedModuleName(component);
759-
760-
var stopwatch = Stopwatch.StartNew();
761-
try
762-
{
763-
var project = component.Collection.Parent;
764-
var projectQualifiedName = new QualifiedModuleName(project);
765-
Declaration projectDeclaration;
766-
if (!_projectDeclarations.TryGetValue(projectQualifiedName.ProjectId, out projectDeclaration))
767-
{
768-
projectDeclaration = CreateProjectDeclaration(projectQualifiedName, project);
769-
_projectDeclarations.AddOrUpdate(projectQualifiedName.ProjectId, projectDeclaration, (s, c) => projectDeclaration);
770-
State.AddDeclaration(projectDeclaration);
771-
}
772-
Logger.Debug("Creating declarations for module {0}.", qualifiedModuleName.Name);
773-
774-
var emitter = new Emitter(_state);
775-
string typeName = null;
776-
if (component.Type == ComponentType.Document)
777-
{
778-
//typeName = emitter.ExecuteWithResult<string>(project, emitter.GetTypeNameFunctionBody(component.Name), "GetTypeName");
779-
}
780-
781-
var declarationsListener = new DeclarationSymbolsListener(State, qualifiedModuleName, component.Type, State.GetModuleAnnotations(component), State.GetModuleAttributes(component), projectDeclaration, typeName);
782-
ParseTreeWalker.Default.Walk(declarationsListener, tree);
783-
foreach (var createdDeclaration in declarationsListener.CreatedDeclarations)
784-
{
785-
State.AddDeclaration(createdDeclaration);
786-
}
787-
}
788-
catch (Exception exception)
789-
{
790-
Logger.Error(exception, "Exception thrown acquiring declarations for '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
791-
State.SetModuleState(component, ParserState.ResolverError);
792-
}
793-
stopwatch.Stop();
794-
Logger.Debug("{0}ms to resolve declarations for component {1}", stopwatch.ElapsedMilliseconds, component.Name);
795-
}
796-
797-
private Declaration CreateProjectDeclaration(QualifiedModuleName projectQualifiedName, IVBProject project)
798-
{
799-
var qualifiedName = projectQualifiedName.QualifyMemberName(project.Name);
800-
var projectId = qualifiedName.QualifiedModuleName.ProjectId;
801-
var projectDeclaration = new ProjectDeclaration(qualifiedName, project.Name, false, project);
802-
803-
var references = new List<ReferencePriorityMap>();
804-
foreach (var item in _projectReferences)
805-
{
806-
if (item.ContainsKey(projectId))
807-
{
808-
references.Add(item);
809-
}
810-
}
811-
812-
foreach (var reference in references)
813-
{
814-
int priority = reference[projectId];
815-
projectDeclaration.AddProjectReference(reference.ReferencedProjectId, priority);
816-
}
817-
return projectDeclaration;
818-
}
819-
820-
private void ResolveReferences(DeclarationFinder finder, IVBComponent component, IParseTree tree)
821-
{
822-
Debug.Assert(State.GetModuleState(component) == ParserState.ResolvingReferences);
823-
824-
var qualifiedName = new QualifiedModuleName(component);
825-
Logger.Debug("Resolving identifier references in '{0}'... (thread {1})", qualifiedName.Name, Thread.CurrentThread.ManagedThreadId);
826-
827-
var resolver = new IdentifierReferenceResolver(qualifiedName, finder);
828-
var listener = new IdentifierReferenceListener(resolver);
829-
830-
if (!string.IsNullOrWhiteSpace(tree.GetText().Trim()))
831-
{
832-
var walker = new ParseTreeWalker();
833-
try
834-
{
835-
var watch = Stopwatch.StartNew();
836-
walker.Walk(listener, tree);
837-
watch.Stop();
838-
Logger.Debug("Binding resolution done for component '{0}' in {1}ms (thread {2})", component.Name,
839-
watch.ElapsedMilliseconds, Thread.CurrentThread.ManagedThreadId);
840-
841-
State.SetModuleState(component, ParserState.Ready);
842-
}
843-
catch (Exception exception)
844-
{
845-
Logger.Error(exception, "Exception thrown resolving '{0}' (thread {1}).", component.Name, Thread.CurrentThread.ManagedThreadId);
846-
State.SetModuleState(component, ParserState.ResolverError);
847-
}
848-
}
849-
}
850-
851750
public void Dispose()
852751
{
853752
State.ParseRequest -= ReparseRequested;
854753
Cancel(false);
855754
}
856755
}
857-
}
756+
}

0 commit comments

Comments
 (0)