Skip to content

Commit

Permalink
Merge branch 'next' into next
Browse files Browse the repository at this point in the history
  • Loading branch information
comintern committed Mar 1, 2017
2 parents 17a7a28 + 359cbcf commit aa59e31
Show file tree
Hide file tree
Showing 19 changed files with 1,153 additions and 814 deletions.
38 changes: 38 additions & 0 deletions RetailCoder.VBE/Common/CodeModuleExtensions.cs
@@ -0,0 +1,38 @@
using Antlr4.Runtime;
using Rubberduck.Parsing.Symbols;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;

namespace Rubberduck.Common
{
public static class CodeModuleExtensions
{
public static void ReplaceToken(this ICodeModule module, IToken token, string replacement)
{
var original = module.GetLines(token.Line, 1);
var result = ReplaceStringAtIndex(original, token.Text, replacement, token.Column);
module.ReplaceLine(token.Line, result);
}

public static void ReplaceIdentifierReferenceName(this ICodeModule module, IdentifierReference identifierReference, string replacement)
{
var original = module.GetLines(identifierReference.Selection.StartLine, 1);
var result = ReplaceStringAtIndex(original, identifierReference.IdentifierName, replacement, identifierReference.Context.Start.Column);
module.ReplaceLine(identifierReference.Selection.StartLine, result);
}

public static void InsertLines(this ICodeModule module, int startLine, string[] lines)
{
int lineNumber = startLine;
for ( int idx = 0; idx < lines.Length; idx++ )
{
module.InsertLines(lineNumber, lines[idx]);
lineNumber++;
}
}
private static string ReplaceStringAtIndex(string original, string toReplace, string replacement, int startIndex)
{
var modifiedContent = original.Remove(startIndex, toReplace.Length);
return modifiedContent.Insert(startIndex, replacement);
}
}
}
Expand Up @@ -6,15 +6,19 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.UI.Refactorings;

namespace Rubberduck.Inspections
{
public sealed class AssignedByValParameterInspection : InspectionBase
{
public AssignedByValParameterInspection(RubberduckParserState state)
private IAssignedByValParameterQuickFixDialogFactory _dialogFactory;
public AssignedByValParameterInspection(RubberduckParserState state, IAssignedByValParameterQuickFixDialogFactory dialogFactory)
: base(state)
{
Severity = DefaultSeverity;
_dialogFactory = dialogFactory;

}

public override string Meta { get { return InspectionsUI.AssignedByValParameterInspectionMeta; } }
Expand All @@ -31,7 +35,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
.ToList();

return parameters
.Select(param => new AssignedByValParameterInspectionResult(this, param))
.Select(param => new AssignedByValParameterInspectionResult(this, param, _dialogFactory))
.ToList();
}
}
Expand Down
@@ -0,0 +1,189 @@
using Rubberduck.Inspections.Abstract;
using System.Linq;
using Rubberduck.Parsing;
using Rubberduck.VBEditor;
using Rubberduck.Inspections.Resources;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using System.Windows.Forms;
using Rubberduck.UI.Refactorings;
using Rubberduck.Common;
using Antlr4.Runtime;
using System.Collections.Generic;
using Antlr4.Runtime.Tree;

namespace Rubberduck.Inspections.QuickFixes
{
public class AssignedByValParameterMakeLocalCopyQuickFix : QuickFixBase
{
private readonly Declaration _target;
private readonly IAssignedByValParameterQuickFixDialogFactory _dialogFactory;
private string _localCopyVariableName;
private string[] _variableNamesAccessibleToProcedureContext;

public AssignedByValParameterMakeLocalCopyQuickFix(Declaration target, QualifiedSelection selection, IAssignedByValParameterQuickFixDialogFactory dialogFactory)
: base(target.Context, selection, InspectionsUI.AssignedByValParameterMakeLocalCopyQuickFix)
{
_target = target;
_dialogFactory = dialogFactory;
_variableNamesAccessibleToProcedureContext = GetVariableNamesAccessibleToProcedureContext(_target.Context.Parent.Parent);
SetValidLocalCopyVariableNameSuggestion();
}

public override bool CanFixInModule { get { return false; } }
public override bool CanFixInProject { get { return false; } }

public override void Fix()
{
RequestLocalCopyVariableName();

if (!VariableNameIsValid(_localCopyVariableName) || IsCancelled)
{
return;
}

ReplaceAssignedByValParameterReferences();

InsertLocalVariableDeclarationAndAssignment();
}

private void RequestLocalCopyVariableName()
{
using( var view = _dialogFactory.Create(_target.IdentifierName, _target.DeclarationType.ToString()))
{
view.NewName = _localCopyVariableName;
view.IdentifierNamesAlreadyDeclared = _variableNamesAccessibleToProcedureContext;
view.ShowDialog();
IsCancelled = view.DialogResult == DialogResult.Cancel;
if (!IsCancelled)
{
_localCopyVariableName = view.NewName;
}
}
}

private void SetValidLocalCopyVariableNameSuggestion()
{
_localCopyVariableName = "x" + _target.IdentifierName.CapitalizeFirstLetter();
if (VariableNameIsValid(_localCopyVariableName)) { return; }

//If the initial suggestion is not valid, keep pre-pending x's until it is
for ( int attempt = 2; attempt < 10; attempt++)
{
_localCopyVariableName = "x" + _localCopyVariableName;
if (VariableNameIsValid(_localCopyVariableName))
{
return;
}
}
//if "xxFoo" to "xxxxxxxxxxFoo" isn't unique, give up and go with the original suggestion.
//The QuickFix will leave the code as-is unless it receives a name that is free of conflicts
_localCopyVariableName = "x" + _target.IdentifierName.CapitalizeFirstLetter();
}

private bool VariableNameIsValid(string variableName)
{
var validator = new VariableNameValidator(variableName);
return validator.IsValidName()
&& !_variableNamesAccessibleToProcedureContext
.Any(name => name.Equals(variableName, System.StringComparison.InvariantCultureIgnoreCase));
}

private void ReplaceAssignedByValParameterReferences()
{
var module = Selection.QualifiedName.Component.CodeModule;
foreach (IdentifierReference identifierReference in _target.References)
{
module.ReplaceIdentifierReferenceName(identifierReference, _localCopyVariableName);
}
}

private void InsertLocalVariableDeclarationAndAssignment()
{
var blocks = QuickFixHelper.GetBlockStmtContextsForContext(_target.Context.Parent.Parent);
string[] lines = { BuildLocalCopyDeclaration(), BuildLocalCopyAssignment() };
var module = Selection.QualifiedName.Component.CodeModule;
module.InsertLines(blocks.FirstOrDefault().Start.Line, lines);
}

private string BuildLocalCopyDeclaration()
{
return Tokens.Dim + " " + _localCopyVariableName + " " + Tokens.As
+ " " + _target.AsTypeName;
}

private string BuildLocalCopyAssignment()
{
return (SymbolList.ValueTypes.Contains(_target.AsTypeName) ? string.Empty : Tokens.Set + " ")
+ _localCopyVariableName + " = " + _target.IdentifierName;
}

private string[] GetVariableNamesAccessibleToProcedureContext(RuleContext ruleContext)
{
var allIdentifiers = new HashSet<string>();

var blocks = QuickFixHelper.GetBlockStmtContextsForContext(ruleContext);

var blockStmtIdentifiers = GetIdentifierNames(blocks);
allIdentifiers.UnionWith(blockStmtIdentifiers);

var args = QuickFixHelper.GetArgContextsForContext(ruleContext);

var potentiallyUnreferencedParameters = GetIdentifierNames(args);
allIdentifiers.UnionWith(potentiallyUnreferencedParameters);

//TODO: add module and global scope variableNames to the list.

return allIdentifiers.ToArray();
}

private HashSet<string> GetIdentifierNames(IReadOnlyList<RuleContext> ruleContexts)
{
var identifiers = new HashSet<string>();
foreach (RuleContext ruleContext in ruleContexts)
{
var identifiersForThisContext = GetIdentifierNames(ruleContext);
identifiers.UnionWith(identifiersForThisContext);
}
return identifiers;
}

private HashSet<string> GetIdentifierNames(RuleContext ruleContext)
{
//Recursively work through the tree to get all IdentifierContexts
var results = new HashSet<string>();
var tokenValues = typeof(Tokens).GetFields().Select(item => item.GetValue(null)).Cast<string>().Select(item => item);
var children = GetChildren(ruleContext);

foreach (IParseTree child in children)
{
if (child is VBAParser.IdentifierContext)
{
var childName = Identifier.GetName((VBAParser.IdentifierContext)child);
if (!tokenValues.Contains(childName))
{
results.Add(childName);
}
}
else
{
if (!(child is TerminalNodeImpl))
{
results.UnionWith(GetIdentifierNames((RuleContext)child));
}
}
}
return results;
}

private static List<IParseTree> GetChildren(RuleContext ruleCtx)
{
var result = new List<IParseTree>();
for (int index = 0; index < ruleCtx.ChildCount; index++)
{
result.Add(ruleCtx.GetChild(index));
}
return result;
}
}
}

0 comments on commit aa59e31

Please sign in to comment.