Skip to content

Commit

Permalink
Address PR #5555 comments
Browse files Browse the repository at this point in the history
Retains use of IModuleRewriterExtensions class.
  • Loading branch information
BZngr committed Aug 14, 2020
1 parent bbf3031 commit 61795ef
Show file tree
Hide file tree
Showing 4 changed files with 35 additions and 29 deletions.
33 changes: 20 additions & 13 deletions Rubberduck.Refactorings/Common/IModuleRewriterExtensions.cs
Expand Up @@ -25,28 +25,32 @@ public static class IModuleRewriterExtensions
/// </remarks>
public static void RemoveVariables(this IModuleRewriter rewriter, IEnumerable<VariableDeclaration> toRemove, bool removeEndOfStmtContext = true)
{
if (!toRemove.Any()) { return; }
if (!toRemove.Any())
{
return;
}

var fieldsByListContext = toRemove.Distinct()
.GroupBy(f => f.Context.GetAncestor<VBAParser.VariableListStmtContext>());
var fieldsToDeleteByListContext = toRemove.Distinct()
.ToLookup(f => f.Context.GetAncestor<VBAParser.VariableListStmtContext>());

foreach (var fieldsGroup in fieldsByListContext)
foreach (var fieldsToDelete in fieldsToDeleteByListContext)
{
var variables = fieldsGroup.Key.children.Where(ch => ch is VBAParser.VariableSubStmtContext);
if (variables.Count() == fieldsGroup.Count())
var variableList = fieldsToDelete.Key.children.OfType<VBAParser.VariableSubStmtContext>();

if (variableList.Count() == fieldsToDelete.Count())
{
if (fieldsGroup.First().ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
if (fieldsToDelete.First().ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
{
rewriter.RemoveDeclaration<VBAParser.ModuleDeclarationsElementContext>(fieldsGroup.First(), removeEndOfStmtContext);
rewriter.RemoveDeclarationContext<VBAParser.ModuleDeclarationsElementContext>(fieldsToDelete.First(), removeEndOfStmtContext);
}
else
{
rewriter.RemoveDeclaration<VBAParser.BlockStmtContext>(fieldsGroup.First(), removeEndOfStmtContext);
rewriter.RemoveDeclarationContext<VBAParser.BlockStmtContext>(fieldsToDelete.First(), removeEndOfStmtContext);
}
continue;
}

foreach (var target in fieldsGroup)
foreach (var target in fieldsToDelete)
{
rewriter.Remove(target);
}
Expand Down Expand Up @@ -76,15 +80,18 @@ public static void RemoveMember(this IModuleRewriter rewriter, ModuleBodyElement
/// </remarks>
public static void RemoveMembers(this IModuleRewriter rewriter, IEnumerable<ModuleBodyElementDeclaration> toRemove, bool removeEndOfStmtContext = true)
{
if (!toRemove.Any()) { return; }
if (!toRemove.Any())
{
return;
}

foreach (var member in toRemove)
{
rewriter.RemoveDeclaration<VBAParser.ModuleBodyElementContext>(member, removeEndOfStmtContext);
rewriter.RemoveDeclarationContext<VBAParser.ModuleBodyElementContext>(member, removeEndOfStmtContext);
}
}

private static void RemoveDeclaration<T>(this IModuleRewriter rewriter, Declaration declaration, bool removeEndOfStmtContext = true) where T : ParserRuleContext
private static void RemoveDeclarationContext<T>(this IModuleRewriter rewriter, Declaration declaration, bool removeEndOfStmtContext = true) where T : ParserRuleContext
{
if (!declaration.Context.TryGetAncestor<T>(out var elementContext))
{
Expand Down
Expand Up @@ -90,23 +90,22 @@ protected override EncapsulateFieldModel InitializeModel(Declaration target)

protected override void RefactorImpl(EncapsulateFieldModel model)
{
var refactorRewriteSession = _rewritingManager.CheckOutCodePaneSession();
var executableRewriteSession = _rewritingManager.CheckOutCodePaneSession();

RefactorRewrite(model, refactorRewriteSession as IRewriteSession);
RefactorRewrite(model, executableRewriteSession);

if (!refactorRewriteSession.TryRewrite())
if (!executableRewriteSession.TryRewrite())
{
throw new RewriteFailedException(refactorRewriteSession);
throw new RewriteFailedException(executableRewriteSession);
}
}

private string PreviewRewrite(EncapsulateFieldModel model)
{
var previewSession = _rewritingManager.CheckOutCodePaneSession() as IRewriteSession;
previewSession = RefactorRewrite(model, previewSession, true);
var previewSession = RefactorRewrite(model, _rewritingManager.CheckOutCodePaneSession(), true);

var rewriter = previewSession.CheckOutModuleRewriter(model.QualifiedModuleName);
return rewriter.GetText();
return previewSession.CheckOutModuleRewriter(model.QualifiedModuleName)
.GetText();
}

private IRewriteSession RefactorRewrite(EncapsulateFieldModel model, IRewriteSession refactorRewriteSession, bool asPreview = false)
Expand Down
Expand Up @@ -22,7 +22,8 @@ protected override void ModifyFields(IRewriteSession refactorRewriteSession)
{
var rewriter = refactorRewriteSession.CheckOutModuleRewriter(_targetQMN);

rewriter.RemoveVariables(SelectedFields.Select(f => f.Declaration).Cast<VariableDeclaration>());
rewriter.RemoveVariables(SelectedFields.Select(f => f.Declaration)
.Cast<VariableDeclaration>());

if (_stateUDTField.IsExistingDeclaration)
{
Expand Down
Expand Up @@ -16,15 +16,14 @@ public MoveCloserToUsageRefactoringAction(IRewritingManager rewritingManager)

protected override void Refactor(MoveCloserToUsageModel model, IRewriteSession rewriteSession)
{
var target = model.Target;
if (target is VariableDeclaration variable)
if (!(model.Target is VariableDeclaration variable))
{
InsertNewDeclaration(variable, rewriteSession);
RemoveOldDeclaration(variable, rewriteSession);
UpdateQualifiedCalls(variable, rewriteSession);
return;
throw new ArgumentException("Invalid type - VariableDeclaration required");
}
throw new ArgumentException("Invalid target declaration type");

InsertNewDeclaration(variable, rewriteSession);
RemoveOldDeclaration(variable, rewriteSession);
UpdateQualifiedCalls(variable, rewriteSession);
}

private void InsertNewDeclaration(VariableDeclaration target, IRewriteSession rewriteSession)
Expand Down

0 comments on commit 61795ef

Please sign in to comment.