Skip to content

Commit

Permalink
Make all places using suspension inspect the result
Browse files Browse the repository at this point in the history
Also contains some naming adjustments based on review comments to PR #5274.
  • Loading branch information
MDoerner committed Nov 26, 2019
1 parent 9be7204 commit 6991bc8
Show file tree
Hide file tree
Showing 7 changed files with 46 additions and 12 deletions.
19 changes: 17 additions & 2 deletions Rubberduck.Core/UI/CodeExplorer/CodeExplorerAddComponentService.cs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
using System;
using System.Linq;
using System.Runtime.ExceptionServices;
using System.Text;
using Rubberduck.Navigation.CodeExplorer;
using Rubberduck.Parsing.VBA;
Expand Down Expand Up @@ -32,10 +33,17 @@ public void AddComponent(CodeExplorerItemViewModel node, ComponentType component

var prefixInModule = FolderAnnotation(node);

_parseManager.OnSuspendParser(
var suspensionResult = _parseManager.OnSuspendParser(
this,
Enum.GetValues(typeof(ParserState)).Cast<ParserState>(),
() => _addComponentService.AddComponent(projectId, componentType, code, prefixInModule));

if (suspensionResult.Outcome == SuspensionOutcome.UnexpectedError
&& suspensionResult.EncounteredException != null)
{
//This rethrows with the original stack trace.
ExceptionDispatchInfo.Capture(suspensionResult.EncounteredException).Throw();
}
}

public void AddComponentWithAttributes(CodeExplorerItemViewModel node, ComponentType componentType, string code, string additionalPrefixInModule = null)
Expand All @@ -60,10 +68,17 @@ public void AddComponentWithAttributes(CodeExplorerItemViewModel node, Component
}
var prefixInModule = modulePrefix.ToString();

_parseManager.OnSuspendParser(
var suspensionResult = _parseManager.OnSuspendParser(
this,
Enum.GetValues(typeof(ParserState)).Cast<ParserState>(),
() => _addComponentService.AddComponentWithAttributes(projectId, componentType, code, prefixInModule));

if (suspensionResult.Outcome == SuspensionOutcome.UnexpectedError
&& suspensionResult.EncounteredException != null)
{
//This rethrows with the original stack trace.
ExceptionDispatchInfo.Capture(suspensionResult.EncounteredException).Throw();
}
}

private string ProjectId(CodeExplorerItemViewModel node)
Expand Down
8 changes: 4 additions & 4 deletions Rubberduck.Core/UI/CodeExplorer/Commands/ImportCommand.cs
Original file line number Diff line number Diff line change
Expand Up @@ -216,7 +216,7 @@ protected void ImportFiles(ICollection<string> filesToImport, IVBProject targetP

var existingModules = Modules(moduleNames, targetProject.ProjectId, finder);

if (!ExistingModulesAreGenerallyOk(existingModules))
if (!ExistingModulesPassPreCheck(existingModules))
{
return;
}
Expand Down Expand Up @@ -274,7 +274,7 @@ protected void ImportFiles(ICollection<string> filesToImport, IVBProject targetP
.Where(module => reImportableComponentTypes.Contains(module.ComponentType))
.ToList();

if (UserDeniesExecution(targetProject))
if (UserDeclinesExecution(targetProject))
{
return;
}
Expand Down Expand Up @@ -303,9 +303,9 @@ protected void ImportFiles(ICollection<string> filesToImport, IVBProject targetP
}
}

protected virtual bool ExistingModulesAreGenerallyOk(IDictionary<string, QualifiedModuleName> existingModules) => true;
protected virtual bool ExistingModulesPassPreCheck(IDictionary<string, QualifiedModuleName> existingModules) => true;
protected virtual ICollection<QualifiedModuleName> ModulesToRemoveBeforeImport(IDictionary<string, QualifiedModuleName> existingModules) => new List<QualifiedModuleName>();
protected virtual bool UserDeniesExecution(IVBProject targetProject) => false;
protected virtual bool UserDeclinesExecution(IVBProject targetProject) => false;

protected bool HasMatchingFileExtension(string filename, QualifiedModuleName module)
{
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ protected override ICollection<QualifiedModuleName> ModulesToRemoveBeforeImport(
.ToHashSet();
}

protected override bool UserDeniesExecution(IVBProject targetProject)
protected override bool UserDeclinesExecution(IVBProject targetProject)
{
return !UserConfirmsToReplaceProjectContents(targetProject);
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ public UpdateFromFilesCommand(
//Since we remove the components, we keep on the safe side.
protected override IEnumerable<string> AlwaysImportableExtensions => Enumerable.Empty<string>();

protected override bool ExistingModulesAreGenerallyOk(IDictionary<string, QualifiedModuleName> existingModules)
protected override bool ExistingModulesPassPreCheck(IDictionary<string, QualifiedModuleName> existingModules)
{
if (!existingModules.All(kvp => HasMatchingFileExtension(kvp.Key, kvp.Value)))
{
Expand Down
2 changes: 1 addition & 1 deletion Rubberduck.Parsing/Rewriter/AttributesRewriteSession.cs
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ protected override bool TryRewriteInternal()
var result = _parseManager.OnSuspendParser(this, new[] {ParserState.Ready, ParserState.ResolvedDeclarations}, ExecuteAllRewriters);
if(result.Outcome != SuspensionOutcome.Completed)
{
Logger.Warn($"Rewriting attribute modules did not succeed. suspension result = {result}");
Logger.Warn($"Rewriting attribute modules did not succeed. Suspension result = {result}");
if (result.EncounteredException != null)
{
Logger.Warn(result.EncounteredException);
Expand Down
2 changes: 0 additions & 2 deletions Rubberduck.Parsing/VBA/IParseManager.cs
Original file line number Diff line number Diff line change
Expand Up @@ -32,8 +32,6 @@ public interface IParseManager : IParserStatusProvider
void MarkAsModified(QualifiedModuleName module);
}



public enum SuspensionOutcome
{
/// <summary>
Expand Down
23 changes: 22 additions & 1 deletion Rubberduck.UnitTesting/UnitTesting/TestEngine.cs
Original file line number Diff line number Diff line change
Expand Up @@ -179,7 +179,28 @@ protected virtual void RunInternal(IEnumerable<TestMethod> tests)
return;
}
//We push the suspension to a background thread to avoid potential deadlocks if a parse is still running.
Task.Run(() => _state.OnSuspendParser(this, AllowedRunStates, () => RunWhileSuspended(tests)));
Task.Run(() =>
{
var suspensionResult = _state.OnSuspendParser(this, AllowedRunStates, () => RunWhileSuspended(tests));
//We have to log and swallow since we run as the top level code in a background thread.
switch (suspensionResult.Outcome)
{
case SuspensionOutcome.Completed:
return;
case SuspensionOutcome.Canceled:
Logger.Debug("Test execution canceled.");
return;
default:
Logger.Warn($"Test execution failed with suspension outcome {suspensionResult.Outcome}.");
if (suspensionResult.EncounteredException != null)
{
Logger.Error(suspensionResult.EncounteredException);
}
return;
}
});
}

private void EnsureRubberduckIsReferencedForEarlyBoundTests()
Expand Down

0 comments on commit 6991bc8

Please sign in to comment.